{-# Language TemplateHaskell, BangPatterns, OverloadedStrings #-}
module Client.State
(
ClientState(..)
, clientWindows
, clientTextBox
, clientTextBoxOffset
, clientConnections
, clientDCC
, clientDCCUpdates
, clientWidth
, clientHeight
, clientEvents
, clientFocus
, clientPrevFocus
, clientExtraFocus
, clientConfig
, clientScroll
, clientDetailView
, clientActivityBar
, clientShowPing
, clientSubfocus
, clientIgnores
, clientIgnoreMask
, clientConnection
, clientBell
, clientExtensions
, clientRegex
, clientLogQueue
, clientActivityReturn
, clientErrorMsg
, clientLayout
, clientRtsStats
, clientConfigPath
, clientStsPolicy
, withClientState
, clientMatcher, Matcher(..), buildMatcher
, clientToggleHideMeta
, clientHighlightsNetwork
, channelUserList
, consumeInput
, currentCompletionList
, identIgnored
, clientFirstLine
, clientLine
, abortNetwork
, addConnection
, removeNetwork
, clientTick
, queueDCCTransfer
, applyMessageToClientState
, clientHighlights
, clientWindowNames
, clientPalette
, clientAutoconnects
, clientActiveCommand
, clientExtraFocuses
, currentNickCompletionMode
, recordChannelMessage
, recordNetworkMessage
, recordError
, recordIrcMessage
, changeFocus
, changeSubfocus
, returnFocus
, advanceFocus
, advanceNetworkFocus
, retreatFocus
, jumpToActivity
, jumpFocus
, setExtraFocus
, scrollClient
, ExtensionState
, esActive
, esMVar
, esStablePtr
, urlPattern
, urlMatches
) where
import Client.CApi
import Client.Commands.WordCompletion
import Client.Configuration
import Client.Configuration.ServerSettings
import Client.Configuration.Sts
import Client.Image.Message
import Client.Image.Palette
import Client.Log
import Client.Mask
import Client.Message
import Client.Network.Async
import Client.State.Channel
import qualified Client.State.EditBox as Edit
import Client.State.Focus
import Client.State.Network
import Client.State.Window
import Client.State.DCC
import Control.Applicative
import Control.Concurrent.MVar
import Control.Concurrent.STM
import Control.Exception
import Control.Lens
import Control.Monad
import Data.Foldable
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HashMap
import Data.HashSet (HashSet)
import qualified Data.HashSet as HashSet
import Data.IntMap (IntMap)
import qualified Data.IntMap as IntMap
import Data.List
import Data.Maybe
import Data.Map (Map)
import qualified Data.Map as Map
import Data.Text (Text)
import qualified Data.Text as Text
import qualified Data.Text.Lazy as LText
import Data.Time
import Foreign.StablePtr
import Irc.Codes
import Irc.Identifier
import Irc.Message
import Irc.RawIrcMsg
import Irc.UserInfo
import LensUtils
import RtsStats (Stats)
import Text.Regex.TDFA
import Text.Regex.TDFA.String (compile)
data ClientState = ClientState
{ _clientWindows :: !(Map Focus Window)
, _clientPrevFocus :: !Focus
, _clientActivityReturn :: !(Maybe Focus)
, _clientFocus :: !Focus
, _clientSubfocus :: !Subfocus
, _clientExtraFocus :: ![Focus]
, _clientConnections :: !(HashMap Text NetworkState)
, _clientEvents :: !(TQueue NetworkEvent)
, _clientDCC :: !DCCState
, _clientDCCUpdates :: !(TChan DCCUpdate)
, _clientConfig :: !Configuration
, _clientConfigPath :: !FilePath
, _clientTextBox :: !Edit.EditBox
, _clientTextBoxOffset :: !Int
, _clientWidth :: !Int
, _clientHeight :: !Int
, _clientScroll :: !Int
, _clientDetailView :: !Bool
, _clientActivityBar :: !Bool
, _clientShowPing :: !Bool
, _clientRegex :: Maybe Matcher
, _clientLayout :: !LayoutMode
, _clientBell :: !Bool
, _clientIgnores :: !(HashSet Identifier)
, _clientIgnoreMask :: Mask
, _clientExtensions :: !ExtensionState
, _clientLogQueue :: ![LogLine]
, _clientErrorMsg :: Maybe Text
, _clientRtsStats :: Maybe Stats
, _clientStsPolicy :: !(HashMap Text StsPolicy)
}
data Matcher = Matcher
{ matcherBefore :: !Int
, matcherAfter :: !Int
, matcherPred :: LText.Text -> Bool
}
data ExtensionState = ExtensionState
{ _esActive :: IntMap ActiveExtension
, _esMVar :: MVar ParkState
, _esStablePtr :: StablePtr (MVar ParkState)
}
type ParkState = (Int,ClientState)
makeLenses ''ClientState
makeLenses ''ExtensionState
clientConnection ::
Applicative f =>
Text ->
LensLike' f ClientState NetworkState
clientConnection network = clientConnections . ix network
clientFirstLine :: ClientState -> String
clientFirstLine = fst . Edit.shift . view (clientTextBox . Edit.content)
clientLine :: ClientState -> (Int, String)
clientLine = views (clientTextBox . Edit.line) (\(Edit.Line n t) -> (n, t))
withClientState :: FilePath -> Configuration -> (ClientState -> IO a) -> IO a
withClientState cfgPath cfg k =
withExtensionState $ \exts ->
do events <- atomically newTQueue
dccEvents <- atomically newTChan
sts <- readPolicyFile
let ignoreIds = map mkId (view configIgnores cfg)
k ClientState
{ _clientWindows = _Empty # ()
, _clientIgnores = HashSet.fromList ignoreIds
, _clientIgnoreMask = buildMask ignoreIds
, _clientConnections = _Empty # ()
, _clientDCC = emptyDCCState
, _clientDCCUpdates = dccEvents
, _clientTextBox = Edit.defaultEditBox
, _clientTextBoxOffset = 0
, _clientWidth = 80
, _clientHeight = 25
, _clientEvents = events
, _clientPrevFocus = Unfocused
, _clientActivityReturn = Nothing
, _clientFocus = Unfocused
, _clientSubfocus = FocusMessages
, _clientExtraFocus = []
, _clientConfig = cfg
, _clientConfigPath = cfgPath
, _clientScroll = 0
, _clientDetailView = False
, _clientRegex = Nothing
, _clientLayout = view configLayout cfg
, _clientActivityBar = view configActivityBar cfg
, _clientShowPing = view configShowPing cfg
, _clientBell = False
, _clientExtensions = exts
, _clientLogQueue = []
, _clientErrorMsg = Nothing
, _clientRtsStats = Nothing
, _clientStsPolicy = sts
}
withExtensionState :: (ExtensionState -> IO a) -> IO a
withExtensionState k =
do mvar <- newEmptyMVar
bracket (newStablePtr mvar) freeStablePtr $ \stab ->
k ExtensionState
{ _esActive = IntMap.empty
, _esMVar = mvar
, _esStablePtr = stab
}
abortNetwork ::
Text ->
ClientState -> IO ClientState
abortNetwork network st =
case preview (clientConnection network) st of
Nothing -> return st
Just cs -> do
abortConnection ForcedDisconnect (view csSocket cs)
return $! over clientConnections (sans network) st
recordChannelMessage ::
Text ->
Identifier ->
ClientMessage ->
ClientState ->
ClientState
recordChannelMessage network channel msg st
= recordLogLine msg channel
$ recordWindowLine focus wl st
where
focus = ChannelFocus network channel'
wl = toWindowLine rendParams importance msg
rendParams = MessageRendererParams
{ rendStatusMsg = statusModes
, rendUserSigils = computeMsgLineSigils network channel' msg st
, rendNicks = HashSet.fromList (channelUserList network channel' st)
, rendMyNicks = highlights
, rendPalette = clientPalette st
, rendAccounts = accounts
}
cs = st ^?! clientConnection network
possibleStatusModes = view csStatusMsg cs
(statusModes, channel') = splitStatusMsgModes possibleStatusModes channel
importance = msgImportance msg st
highlights = clientHighlightsNetwork network st
accounts =
if view (csSettings . ssShowAccounts) cs
then view csUsers cs
else HashMap.empty
recordLogLine ::
ClientMessage ->
Identifier ->
ClientState ->
ClientState
recordLogLine msg target st =
case view (clientConnection (view msgNetwork msg) . csSettings . ssLogDir) st of
Nothing -> st
Just dir ->
case renderLogLine msg dir target of
Nothing -> st
Just ll -> over clientLogQueue (cons ll) st
splitStatusMsgModes ::
[Char] ->
Identifier ->
([Char], Identifier)
splitStatusMsgModes possible ident = (Text.unpack modes, mkId ident')
where
(modes, ident') = Text.span (`elem` possible) (idText ident)
msgImportance :: ClientMessage -> ClientState -> WindowLineImportance
msgImportance msg st =
let network = view msgNetwork msg
me = preview (clientConnection network . csNick) st
highlights = clientHighlightsNetwork network st
isMe x = Just x == me
checkTxt txt
| any (\x -> HashSet.member (mkId x) highlights)
(nickSplit txt) = WLImportant
| otherwise = WLNormal
in
case view msgBody msg of
NormalBody{} -> WLImportant
ErrorBody{} -> WLImportant
IrcBody irc
| squelchIrcMsg irc -> WLBoring
| isJust (ircIgnorable irc st) -> WLBoring
| otherwise ->
case irc of
Privmsg _ tgt txt
| isMe tgt -> WLImportant
| otherwise -> checkTxt txt
Notice _ tgt txt
| isMe tgt -> WLImportant
| otherwise -> checkTxt txt
Ctcp _ tgt "ACTION" txt
| isMe tgt -> WLImportant
| otherwise -> checkTxt txt
Ctcp{} -> WLNormal
Part who _ _ | isMe (userNick who) -> WLImportant
| otherwise -> WLBoring
Kick _ _ kicked _ | isMe kicked -> WLImportant
| otherwise -> WLNormal
Error{} -> WLImportant
Reply RPL_TOPIC _ -> WLBoring
Reply RPL_INVITING _ -> WLBoring
Reply cmd _ ->
case replyCodeType (replyCodeInfo cmd) of
ErrorReply -> WLImportant
_ -> WLNormal
_ -> WLBoring
ircIgnorable :: IrcMsg -> ClientState -> Maybe Identifier
ircIgnorable msg !st =
case msg of
Privmsg who _ _ -> checkUser who
Notice who _ _ -> checkUser who
Ctcp who _ "ACTION" _ -> checkUser who
CtcpNotice who _ _ _ -> checkUser who
_ -> Nothing
where
checkUser !who
| identIgnored who st = Just (userNick who)
| otherwise = Nothing
identIgnored ::
UserInfo ->
ClientState ->
Bool
identIgnored who st = matchMask (view clientIgnoreMask st) who
recordIrcMessage ::
Text ->
MessageTarget ->
ClientMessage ->
ClientState -> ClientState
recordIrcMessage network target msg st =
updateTransientError (NetworkFocus network) msg $
case target of
TargetHidden -> st
TargetNetwork -> recordNetworkMessage msg st
TargetWindow chan -> recordChannelMessage network chan msg st
TargetUser user ->
foldl' (\st' chan -> overStrict
(clientWindows . ix (ChannelFocus network chan))
(addToWindow wl) st')
st chans
where
cfg = view clientConfig st
wl = toWindowLine' cfg WLBoring msg
chans = user
: case preview (clientConnection network . csChannels) st of
Nothing -> []
Just m -> [chan | (chan, cs) <- HashMap.toList m
, HashMap.member user (view chanUsers cs) ]
computeMsgLineSigils ::
Text ->
Identifier ->
ClientMessage ->
ClientState ->
[Char]
computeMsgLineSigils network channel msg st =
case msgActor =<< preview (msgBody . _IrcBody) msg of
Just user -> computeUserSigils network channel (userNick user) st
Nothing -> []
computeUserSigils ::
Text ->
Identifier ->
Identifier ->
ClientState ->
[Char]
computeUserSigils network channel user =
view $ clientConnection network
. csChannels . ix channel
. chanUsers . ix user
updateTransientError :: Focus -> ClientMessage -> ClientState -> ClientState
updateTransientError destination msg st
| view clientFocus st == destination = st
| otherwise =
let err e = set clientErrorMsg (Just e) st in
case view msgBody msg of
ErrorBody txt -> err txt
IrcBody (Error txt) -> err txt
IrcBody (Reply code args)
| let info = replyCodeInfo code
, ErrorReply <- replyCodeType info ->
err (Text.intercalate " " (replyCodeText info : drop 1 args))
_ -> st
recordNetworkMessage :: ClientMessage -> ClientState -> ClientState
recordNetworkMessage msg st = updateTransientError focus msg
$ recordWindowLine focus wl st
where
network = view msgNetwork msg
focus | Text.null network = Unfocused
| otherwise = NetworkFocus (view msgNetwork msg)
importance = msgImportance msg st
wl = toWindowLine' cfg importance msg
cfg = view clientConfig st
recordError ::
ZonedTime ->
Text ->
Text ->
ClientState ->
ClientState
recordError now net msg =
recordNetworkMessage ClientMessage
{ _msgTime = now
, _msgNetwork = net
, _msgBody = ErrorBody msg
}
recordWindowLine ::
Focus ->
WindowLine ->
ClientState ->
ClientState
recordWindowLine focus wl st = st2
where
freshWindow = emptyWindow { _winHideMeta = view (clientConfig . configHideMeta) st }
st1 = over (clientWindows . at focus)
(\w -> Just $! addToWindow wl (fromMaybe freshWindow w))
st
st2
| not (view clientBell st)
, view (clientConfig . configBellOnMention) st
, view wlImportance wl == WLImportant
, not (hasMention st) = set clientBell True st1
| otherwise = st1
hasMention = elemOf (clientWindows . folded . winMention) WLImportant
toWindowLine :: MessageRendererParams -> WindowLineImportance -> ClientMessage -> WindowLine
toWindowLine params importance msg = WindowLine
{ _wlSummary = msgSummary (view msgBody msg)
, _wlPrefix = prefix
, _wlImage = image
, _wlFullImage = full
, _wlImportance = importance
, _wlTimestamp = views msgTime packZonedTime msg
}
where
(prefix, image, full) = msgImage (view msgTime msg) params (view msgBody msg)
toWindowLine' :: Configuration -> WindowLineImportance -> ClientMessage -> WindowLine
toWindowLine' config =
toWindowLine defaultRenderParams
{ rendPalette = view configPalette config
, rendMyNicks = view configExtraHighlights config
}
clientTick :: ClientState -> ClientState
clientTick = set clientBell False
. markSeen
. set clientLogQueue []
markSeen :: ClientState -> ClientState
markSeen st =
case view clientSubfocus st of
FocusMessages -> foldl' aux st focuses
_ -> st
where
aux acc focus = overStrict (clientWindows . ix focus) windowSeen acc
focuses = view clientFocus st
: view clientExtraFocus st
consumeInput :: ClientState -> ClientState
consumeInput = over clientTextBox Edit.success
currentCompletionList :: ClientState -> [Identifier]
currentCompletionList st =
case view clientFocus st of
NetworkFocus network -> networkChannelList network st
ChannelFocus network chan ->
chan
: networkChannelList network st
++ channelUserList network chan st
_ -> []
currentNickCompletionMode :: ClientState -> WordCompletionMode
currentNickCompletionMode st =
fromMaybe defaultNickWordCompleteMode $
do network <- views clientFocus focusNetwork st
preview (clientConnection network . csSettings . ssNickCompletion) st
networkChannelList ::
Text ->
ClientState ->
[Identifier]
networkChannelList network =
views (clientConnection network . csChannels) HashMap.keys
channelUserList ::
Text ->
Identifier ->
ClientState ->
[Identifier]
channelUserList network channel =
views (clientConnection network . csChannels . ix channel . chanUsers) HashMap.keys
clientMatcher ::
ClientState ->
Maybe Matcher
clientMatcher st =
case clientActiveCommand st of
Just ("grep" , reStr) -> buildMatcher reStr
_ -> case view clientRegex st of
Nothing -> Nothing
Just r -> Just r
buildMatcher :: String -> Maybe Matcher
buildMatcher = go (True, 0, 0)
where
go (sensitive, b, a) reStr =
case dropWhile (' '==) reStr of
'-' : 'i' : ' ' : reStr' -> go (False, b, a) reStr'
'-' : 'A' : reStr' | [(a' , ' ':reStr'')] <- reads reStr', a' >= 0 -> go (sensitive, b, a') reStr''
'-' : 'B' : reStr' | [(b' , ' ':reStr'')] <- reads reStr', b' >= 0 -> go (sensitive, b', a) reStr''
'-' : 'C' : reStr' | [(num, ' ':reStr'')] <- reads reStr', num >= 0 -> go (sensitive, num, num) reStr''
'-' : '-' : reStr' -> finish (sensitive, b, a) (drop 1 reStr')
_ -> finish (sensitive, b, a) reStr
finish (sensitive, b, a) reStr =
case compile defaultCompOpt{caseSensitive=sensitive}
defaultExecOpt{captureGroups=False}
reStr of
Left{} -> Nothing
Right r -> Just (Matcher b a (matchTest r . LText.unpack))
clientActiveCommand ::
ClientState ->
Maybe (String,String)
clientActiveCommand st =
case break (==' ') (clientFirstLine st) of
('/':cmd,_:args) -> Just (cmd,args)
_ -> Nothing
urlPattern :: Regex
Right urlPattern =
compile
defaultCompOpt
defaultExecOpt{captureGroups=False}
"https?://([[:alnum:]-]+\\.)*([[:alnum:]-]+)(:[[:digit:]]+)?(/[-0-9a-zA-Z$_.+!*'(),%?&=:@/;~#]*)?|\
\<https?://[^>]*>|\
\\\(https?://[^\\)]*\\)"
urlMatches :: LText.Text -> [Text]
urlMatches txt = removeBrackets . extractText . (^?! ix 0)
<$> matchAll urlPattern (LText.unpack txt)
where
extractText (off,len) = LText.toStrict
$ LText.take (fromIntegral len)
$ LText.drop (fromIntegral off) txt
removeBrackets t =
case Text.uncons t of
Just ('<',t') | not (Text.null t') -> Text.init t'
Just ('(',t') | not (Text.null t') -> Text.init t'
_ -> t
removeNetwork :: Text -> ClientState -> (NetworkState, ClientState)
removeNetwork network st =
case (clientConnections . at network <<.~ Nothing) st of
(Nothing, _ ) -> error "removeNetwork: network not found"
(Just cs, st1) -> (cs, st1)
addConnection ::
Int ->
Maybe UTCTime ->
Maybe Int ->
Text ->
ClientState ->
IO ClientState
addConnection attempts lastTime stsUpgrade network st =
do let defSettings = (view (clientConfig . configDefaults) st)
{ _ssName = Just network
, _ssHostName = Text.unpack network
}
settings = fromMaybe defSettings
$ preview (clientConfig . configServers . ix network) st
now <- getCurrentTime
let stsUpgrade'
| Just{} <- stsUpgrade = stsUpgrade
| UseInsecure <- view ssTls settings
, let host = Text.pack (view ssHostName settings)
, Just policy <- view (clientStsPolicy . at host) st
, now < view stsExpiration policy
= Just (view stsPort policy)
| otherwise = Nothing
settings1 =
case stsUpgrade' of
Just port -> set ssPort (Just (fromIntegral port))
$ set ssTls UseTls settings
Nothing -> settings
delay = 15 * max 0 (attempts - 1)
c <- createConnection
delay
settings1
let cs = newNetworkState network settings1 c (PingConnecting attempts lastTime)
traverse_ (sendMsg cs) (initialMessages cs)
return $ set (clientConnections . at network) (Just cs) st
applyMessageToClientState ::
ZonedTime ->
IrcMsg ->
Text ->
NetworkState ->
ClientState ->
([RawIrcMsg], Maybe DCCUpdate, ClientState)
applyMessageToClientState time irc network cs st =
cs' `seq` (reply, dccUp, st')
where
(reply, cs') = applyMessage time irc cs
(st', dccUp) = queueDCCTransfer network irc
$ applyWindowRenames network irc
$ set (clientConnections . ix network) cs' st
queueDCCTransfer :: Text -> IrcMsg -> ClientState
-> (ClientState, Maybe DCCUpdate)
queueDCCTransfer network ctcpMsg st
| Just (fromU, _target, command, txt) <- ctcpToTuple ctcpMsg
, command == "DCC", dccState <- view clientDCC st
= case (parseSEND network fromU txt, parseACCEPT dccState fromU txt) of
(Right offer, _) -> (set clientDCC (insertAsNewMax offer dccState) st, Nothing)
(_, Just upd) -> (st, Just upd)
(_, _) -> (st, Nothing)
| otherwise = (st, Nothing)
applyWindowRenames ::
Text ->
IrcMsg ->
ClientState -> ClientState
applyWindowRenames network (Nick old new) st
| hasWindow old'
, not (hasWindow new) = over clientFocus moveFocus
$ over clientWindows moveWindow st
| otherwise = st
where
old' = userNick old
mkFocus = ChannelFocus network
hasWindow who = has (clientWindows . ix (mkFocus who)) st
moveWindow :: Map Focus Window -> Map Focus Window
moveWindow wins =
let (win,wins') = (at (mkFocus old') <<.~ Nothing) wins
in set (at (mkFocus new)) win wins'
moveFocus x
| x == mkFocus old' = mkFocus new
| otherwise = x
applyWindowRenames _ _ st = st
scrollClient :: Int -> ClientState -> ClientState
scrollClient amt = over clientScroll $ \n -> max 0 (n + amt)
clientExtraFocuses :: ClientState -> [Focus]
clientExtraFocuses st =
case view clientSubfocus st of
FocusMessages -> view clientFocus st `delete` view clientExtraFocus st
_ -> []
jumpToActivity :: ClientState -> ClientState
jumpToActivity st =
case mplus highPriority lowPriority of
Just (focus,_) -> changeFocus focus st
Nothing ->
case view clientActivityReturn st of
Just focus -> changeFocus focus st
Nothing -> st
where
windowList = views clientWindows Map.toAscList st
highPriority = find (\x -> WLImportant == view winMention (snd x)) windowList
lowPriority = find (\x -> view winUnread (snd x) > 0) windowList
jumpFocus ::
Int ->
ClientState -> ClientState
jumpFocus i st
| 0 <= i, i < Map.size windows = changeFocus focus st
| otherwise = st
where
windows = view clientWindows st
(focus,_) = Map.elemAt i windows
changeFocus ::
Focus ->
ClientState ->
ClientState
changeFocus focus st
= set clientScroll 0
. activateCurrent
. deactivatePrevious
. updatePrevious
. set clientFocus focus
. set clientSubfocus FocusMessages
$ st
where
oldFocus = view clientFocus st
updatePrevious
| focus == oldFocus = id
| otherwise = set clientPrevFocus oldFocus
activateCurrent = over (clientWindows . ix focus) windowActivate
deactivatePrevious
| oldFocus `elem` focus : view clientExtraFocus st = id
| otherwise = over (clientWindows . ix oldFocus) windowDeactivate
setExtraFocus :: [Focus] -> ClientState -> ClientState
setExtraFocus newFocuses st
= aux windowDeactivate newlyInactive
$ aux windowActivate newlyActive
$ set clientExtraFocus newFocuses st
where
newlyActive = newFocuses \\ (view clientFocus st : view clientExtraFocus st)
newlyInactive = view clientExtraFocus st \\ (view clientFocus st : newFocuses)
aux f xs st1 =
foldl' (\acc w -> overStrict (clientWindows . ix w) f acc) st1 xs
changeSubfocus ::
Subfocus ->
ClientState ->
ClientState
changeSubfocus focus
= set clientErrorMsg Nothing
. set clientScroll 0
. set clientSubfocus focus
returnFocus :: ClientState -> ClientState
returnFocus st = changeFocus (view clientPrevFocus st) st
advanceFocus :: ClientState -> ClientState
advanceFocus = stepFocus $ \l r ->
fst . fst <$> Map.minViewWithKey r <|>
fst . fst <$> Map.minViewWithKey l
retreatFocus :: ClientState -> ClientState
retreatFocus = stepFocus $ \l r ->
fst . fst <$> Map.maxViewWithKey l <|>
fst . fst <$> Map.maxViewWithKey r
advanceNetworkFocus :: ClientState -> ClientState
advanceNetworkFocus = stepFocus $ \l r ->
fst . fst <$> Map.minViewWithKey (Map.filterWithKey isNetwork r) <|>
fst . fst <$> Map.minViewWithKey (Map.filterWithKey isNetwork l)
where
isNetwork k _ = has _NetworkFocus k
type FocusSelector =
Map Focus Window ->
Map Focus Window ->
Maybe Focus
stepFocus ::
FocusSelector ->
ClientState ->
ClientState
stepFocus selector st =
case selector l r of
Just k -> changeFocus k st
Nothing -> st
where
(l,r) = Map.split (view clientFocus st) (view clientWindows st)
clientHighlights ::
NetworkState ->
ClientState ->
HashSet Identifier
clientHighlights cs st =
HashSet.insert
(view csNick cs)
(view (clientConfig . configExtraHighlights) st)
clientHighlightsNetwork ::
Text ->
ClientState ->
HashSet Identifier
clientHighlightsNetwork network st =
case preview (clientConnection network) st of
Just cs -> clientHighlights cs st
Nothing -> view (clientConfig . configExtraHighlights) st
clientWindowNames ::
ClientState ->
[Char]
clientWindowNames = views (clientConfig . configWindowNames) Text.unpack
clientPalette :: ClientState -> Palette
clientPalette = view (clientConfig . configPalette)
clientAutoconnects :: ClientState -> [Text]
clientAutoconnects st =
[ network | (network, cfg) <- views (clientConfig . configServers) HashMap.toList st
, view ssAutoconnect cfg
]
clientToggleHideMeta :: ClientState -> ClientState
clientToggleHideMeta st =
overStrict (clientWindows . ix (view clientFocus st) . winHideMeta) not st