{-# Language OverloadedStrings, TemplateHaskell #-}
module Client.Commands.Channel (channelCommands) where
import Client.Commands.Arguments.Spec
import Client.Commands.Docs (chanopDocs, cmdDoc)
import Client.Commands.TabCompletion (activeNicks, noChannelTab, simpleChannelTab, simpleTabCompletion)
import Client.Commands.Types
import Client.Commands.WordCompletion (plainWordCompleteMode)
import Client.State
import Client.State.Channel (chanLists, chanModes, chanTopic, chanUsers)
import Client.State.EditBox qualified as Edit
import Client.State.Focus
import Client.State.Network
import Client.UserHost ( UserAndHost(UserAndHost) )
import Control.Applicative (liftA2)
import Control.Lens
import Control.Monad (unless)
import Data.Foldable (traverse_)
import Data.HashMap.Strict qualified as HashMap
import Data.List.Split (chunksOf)
import Data.Maybe (fromMaybe, maybeToList)
import Data.Text (Text)
import Data.Text qualified as Text
import Irc.Commands (ircInvite, ircKick, ircMode, ircPrivmsg, ircRemove)
import Irc.Identifier (Identifier, mkId, idText)
import Irc.Modes
import Irc.Message (isNickChar)
import Irc.UserInfo (UserInfo(UserInfo), renderUserInfo)
channelCommands :: CommandSection
channelCommands :: CommandSection
channelCommands = Text -> [Command] -> CommandSection
CommandSection Text
"IRC channel management"
[ NonEmpty Text
-> Args ArgsContext [[Char]]
-> Text
-> CommandImpl [[Char]]
-> Command
forall a.
NonEmpty Text
-> Args ArgsContext a -> Text -> CommandImpl a -> Command
Command
(Text -> NonEmpty Text
forall a. a -> NonEmpty a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
"mode")
([[Char]] -> Maybe [[Char]] -> [[Char]]
forall a. a -> Maybe a -> a
fromMaybe [] (Maybe [[Char]] -> [[Char]])
-> Ap (Arg ArgsContext) (Maybe [[Char]])
-> Args ArgsContext [[Char]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Args ArgsContext [[Char]] -> Ap (Arg ArgsContext) (Maybe [[Char]])
forall r a. Args r a -> Args r (Maybe a)
optionalArg ([Char]
-> (ArgsContext -> [Char] -> Maybe (Args ArgsContext [[Char]]))
-> Args ArgsContext [[Char]]
forall r a. [Char] -> (r -> [Char] -> Maybe (Args r a)) -> Args r a
extensionArg [Char]
"[modes]" ArgsContext -> [Char] -> Maybe (Args ArgsContext [[Char]])
modeParamArgs))
$(chanopDocs `cmdDoc` "mode")
(CommandImpl [[Char]] -> Command)
-> CommandImpl [[Char]] -> Command
forall a b. (a -> b) -> a -> b
$ MaybeChatCommand [[Char]]
-> (Bool -> MaybeChatCommand [Char]) -> CommandImpl [[Char]]
forall a.
MaybeChatCommand a
-> (Bool -> MaybeChatCommand [Char]) -> CommandImpl a
MaybeChatCommand MaybeChatCommand [[Char]]
cmdMode Bool -> MaybeChatCommand [Char]
tabMode
, NonEmpty Text
-> Args ArgsContext [Char] -> Text -> CommandImpl [Char] -> Command
forall a.
NonEmpty Text
-> Args ArgsContext a -> Text -> CommandImpl a -> Command
Command
(Text -> NonEmpty Text
forall a. a -> NonEmpty a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
"masks")
([Char] -> Args ArgsContext [Char]
forall r. [Char] -> Args r [Char]
simpleToken [Char]
"mode")
$(chanopDocs `cmdDoc` "masks")
(CommandImpl [Char] -> Command) -> CommandImpl [Char] -> Command
forall a b. (a -> b) -> a -> b
$ ChannelCommand [Char]
-> (Bool -> ChannelCommand [Char]) -> CommandImpl [Char]
forall a.
ChannelCommand a
-> (Bool -> ChannelCommand [Char]) -> CommandImpl a
ChannelCommand ChannelCommand [Char]
cmdMasks Bool -> ChannelCommand [Char]
noChannelTab
, NonEmpty Text
-> Args ArgsContext [Char] -> Text -> CommandImpl [Char] -> Command
forall a.
NonEmpty Text
-> Args ArgsContext a -> Text -> CommandImpl a -> Command
Command
(Text -> NonEmpty Text
forall a. a -> NonEmpty a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
"invite")
([Char] -> Args ArgsContext [Char]
forall r. [Char] -> Args r [Char]
simpleToken [Char]
"nick")
$(chanopDocs `cmdDoc` "invite")
(CommandImpl [Char] -> Command) -> CommandImpl [Char] -> Command
forall a b. (a -> b) -> a -> b
$ ChannelCommand [Char]
-> (Bool -> ChannelCommand [Char]) -> CommandImpl [Char]
forall a.
ChannelCommand a
-> (Bool -> ChannelCommand [Char]) -> CommandImpl a
ChannelCommand ChannelCommand [Char]
cmdInvite Bool -> ChannelCommand [Char]
simpleChannelTab
, NonEmpty Text
-> Args ArgsContext [Char] -> Text -> CommandImpl [Char] -> Command
forall a.
NonEmpty Text
-> Args ArgsContext a -> Text -> CommandImpl a -> Command
Command
(Text -> NonEmpty Text
forall a. a -> NonEmpty a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
"topic")
([Char] -> Args ArgsContext [Char]
forall r. [Char] -> Args r [Char]
remainingArg [Char]
"message")
$(chanopDocs `cmdDoc` "topic")
(CommandImpl [Char] -> Command) -> CommandImpl [Char] -> Command
forall a b. (a -> b) -> a -> b
$ ChannelCommand [Char]
-> (Bool -> ChannelCommand [Char]) -> CommandImpl [Char]
forall a.
ChannelCommand a
-> (Bool -> ChannelCommand [Char]) -> CommandImpl a
ChannelCommand ChannelCommand [Char]
cmdTopic Bool -> ChannelCommand [Char]
tabTopic
, NonEmpty Text
-> Args ArgsContext ([Char], [Char])
-> Text
-> CommandImpl ([Char], [Char])
-> Command
forall a.
NonEmpty Text
-> Args ArgsContext a -> Text -> CommandImpl a -> Command
Command
(Text -> NonEmpty Text
forall a. a -> NonEmpty a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
"kick")
(([Char] -> [Char] -> ([Char], [Char]))
-> Args ArgsContext [Char]
-> Args ArgsContext [Char]
-> Args ArgsContext ([Char], [Char])
forall a b c.
(a -> b -> c)
-> Ap (Arg ArgsContext) a
-> Ap (Arg ArgsContext) b
-> Ap (Arg ArgsContext) c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (,) ([Char] -> Args ArgsContext [Char]
forall r. [Char] -> Args r [Char]
simpleToken [Char]
"nick") ([Char] -> Args ArgsContext [Char]
forall r. [Char] -> Args r [Char]
remainingArg [Char]
"reason"))
$(chanopDocs `cmdDoc` "kick")
(CommandImpl ([Char], [Char]) -> Command)
-> CommandImpl ([Char], [Char]) -> Command
forall a b. (a -> b) -> a -> b
$ ChannelCommand ([Char], [Char])
-> (Bool -> ChannelCommand [Char]) -> CommandImpl ([Char], [Char])
forall a.
ChannelCommand a
-> (Bool -> ChannelCommand [Char]) -> CommandImpl a
ChannelCommand ChannelCommand ([Char], [Char])
cmdKick Bool -> ChannelCommand [Char]
simpleChannelTab
, NonEmpty Text
-> Args ArgsContext ([Char], [Char])
-> Text
-> CommandImpl ([Char], [Char])
-> Command
forall a.
NonEmpty Text
-> Args ArgsContext a -> Text -> CommandImpl a -> Command
Command
(Text -> NonEmpty Text
forall a. a -> NonEmpty a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
"kickban")
(([Char] -> [Char] -> ([Char], [Char]))
-> Args ArgsContext [Char]
-> Args ArgsContext [Char]
-> Args ArgsContext ([Char], [Char])
forall a b c.
(a -> b -> c)
-> Ap (Arg ArgsContext) a
-> Ap (Arg ArgsContext) b
-> Ap (Arg ArgsContext) c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (,) ([Char] -> Args ArgsContext [Char]
forall r. [Char] -> Args r [Char]
simpleToken [Char]
"nick") ([Char] -> Args ArgsContext [Char]
forall r. [Char] -> Args r [Char]
remainingArg [Char]
"reason"))
$(chanopDocs `cmdDoc` "kickban")
(CommandImpl ([Char], [Char]) -> Command)
-> CommandImpl ([Char], [Char]) -> Command
forall a b. (a -> b) -> a -> b
$ ChannelCommand ([Char], [Char])
-> (Bool -> ChannelCommand [Char]) -> CommandImpl ([Char], [Char])
forall a.
ChannelCommand a
-> (Bool -> ChannelCommand [Char]) -> CommandImpl a
ChannelCommand ChannelCommand ([Char], [Char])
cmdKickBan Bool -> ChannelCommand [Char]
simpleChannelTab
, NonEmpty Text
-> Args ArgsContext [Char] -> Text -> CommandImpl [Char] -> Command
forall a.
NonEmpty Text
-> Args ArgsContext a -> Text -> CommandImpl a -> Command
Command
(Text -> NonEmpty Text
forall a. a -> NonEmpty a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
"quiet")
([Char] -> Args ArgsContext [Char]
forall r. [Char] -> Args r [Char]
simpleToken [Char]
"nick|mask")
$(chanopDocs `cmdDoc` "quiet")
(CommandImpl [Char] -> Command) -> CommandImpl [Char] -> Command
forall a b. (a -> b) -> a -> b
$ ChannelCommand [Char]
-> (Bool -> ChannelCommand [Char]) -> CommandImpl [Char]
forall a.
ChannelCommand a
-> (Bool -> ChannelCommand [Char]) -> CommandImpl a
ChannelCommand ChannelCommand [Char]
cmdQuiet Bool -> ChannelCommand [Char]
simpleChannelTab
, NonEmpty Text
-> Args ArgsContext ([Char], [Char])
-> Text
-> CommandImpl ([Char], [Char])
-> Command
forall a.
NonEmpty Text
-> Args ArgsContext a -> Text -> CommandImpl a -> Command
Command
(Text -> NonEmpty Text
forall a. a -> NonEmpty a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
"remove")
(([Char] -> [Char] -> ([Char], [Char]))
-> Args ArgsContext [Char]
-> Args ArgsContext [Char]
-> Args ArgsContext ([Char], [Char])
forall a b c.
(a -> b -> c)
-> Ap (Arg ArgsContext) a
-> Ap (Arg ArgsContext) b
-> Ap (Arg ArgsContext) c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (,) ([Char] -> Args ArgsContext [Char]
forall r. [Char] -> Args r [Char]
simpleToken [Char]
"nick") ([Char] -> Args ArgsContext [Char]
forall r. [Char] -> Args r [Char]
remainingArg [Char]
"reason"))
$(chanopDocs `cmdDoc` "remove")
(CommandImpl ([Char], [Char]) -> Command)
-> CommandImpl ([Char], [Char]) -> Command
forall a b. (a -> b) -> a -> b
$ ChannelCommand ([Char], [Char])
-> (Bool -> ChannelCommand [Char]) -> CommandImpl ([Char], [Char])
forall a.
ChannelCommand a
-> (Bool -> ChannelCommand [Char]) -> CommandImpl a
ChannelCommand ChannelCommand ([Char], [Char])
cmdRemove Bool -> ChannelCommand [Char]
simpleChannelTab
, NonEmpty Text
-> Args ArgsContext (Maybe [Char])
-> Text
-> CommandImpl (Maybe [Char])
-> Command
forall a.
NonEmpty Text
-> Args ArgsContext a -> Text -> CommandImpl a -> Command
Command
(Text -> NonEmpty Text
forall a. a -> NonEmpty a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
"op")
(Args ArgsContext [Char] -> Args ArgsContext (Maybe [Char])
forall r a. Args r a -> Args r (Maybe a)
optionalArg (Args ArgsContext [Char] -> Args ArgsContext (Maybe [Char]))
-> Args ArgsContext [Char] -> Args ArgsContext (Maybe [Char])
forall a b. (a -> b) -> a -> b
$ [Char] -> Args ArgsContext [Char]
forall r. [Char] -> Args r [Char]
simpleToken [Char]
"[nick]")
$(chanopDocs `cmdDoc` "op")
(CommandImpl (Maybe [Char]) -> Command)
-> CommandImpl (Maybe [Char]) -> Command
forall a b. (a -> b) -> a -> b
$ ChannelCommand (Maybe [Char])
-> (Bool -> ChannelCommand [Char]) -> CommandImpl (Maybe [Char])
forall a.
ChannelCommand a
-> (Bool -> ChannelCommand [Char]) -> CommandImpl a
ChannelCommand (Text -> Text -> ChannelCommand (Maybe [Char])
cmdStatus Text
"OP" Text
"+o") Bool -> ChannelCommand [Char]
simpleChannelTab
, NonEmpty Text
-> Args ArgsContext (Maybe [Char])
-> Text
-> CommandImpl (Maybe [Char])
-> Command
forall a.
NonEmpty Text
-> Args ArgsContext a -> Text -> CommandImpl a -> Command
Command
(Text -> NonEmpty Text
forall a. a -> NonEmpty a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
"deop")
(Args ArgsContext [Char] -> Args ArgsContext (Maybe [Char])
forall r a. Args r a -> Args r (Maybe a)
optionalArg (Args ArgsContext [Char] -> Args ArgsContext (Maybe [Char]))
-> Args ArgsContext [Char] -> Args ArgsContext (Maybe [Char])
forall a b. (a -> b) -> a -> b
$ [Char] -> Args ArgsContext [Char]
forall r. [Char] -> Args r [Char]
simpleToken [Char]
"[nick]")
$(chanopDocs `cmdDoc` "deop")
(CommandImpl (Maybe [Char]) -> Command)
-> CommandImpl (Maybe [Char]) -> Command
forall a b. (a -> b) -> a -> b
$ ChannelCommand (Maybe [Char])
-> (Bool -> ChannelCommand [Char]) -> CommandImpl (Maybe [Char])
forall a.
ChannelCommand a
-> (Bool -> ChannelCommand [Char]) -> CommandImpl a
ChannelCommand (Text -> Text -> ChannelCommand (Maybe [Char])
cmdStatus Text
"DEOP" Text
"-o") Bool -> ChannelCommand [Char]
simpleChannelTab
, NonEmpty Text
-> Args ArgsContext (Maybe [Char])
-> Text
-> CommandImpl (Maybe [Char])
-> Command
forall a.
NonEmpty Text
-> Args ArgsContext a -> Text -> CommandImpl a -> Command
Command
(Text -> NonEmpty Text
forall a. a -> NonEmpty a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
"voice")
(Args ArgsContext [Char] -> Args ArgsContext (Maybe [Char])
forall r a. Args r a -> Args r (Maybe a)
optionalArg (Args ArgsContext [Char] -> Args ArgsContext (Maybe [Char]))
-> Args ArgsContext [Char] -> Args ArgsContext (Maybe [Char])
forall a b. (a -> b) -> a -> b
$ [Char] -> Args ArgsContext [Char]
forall r. [Char] -> Args r [Char]
simpleToken [Char]
"[nick]")
$(chanopDocs `cmdDoc` "voice")
(CommandImpl (Maybe [Char]) -> Command)
-> CommandImpl (Maybe [Char]) -> Command
forall a b. (a -> b) -> a -> b
$ ChannelCommand (Maybe [Char])
-> (Bool -> ChannelCommand [Char]) -> CommandImpl (Maybe [Char])
forall a.
ChannelCommand a
-> (Bool -> ChannelCommand [Char]) -> CommandImpl a
ChannelCommand (Text -> Text -> ChannelCommand (Maybe [Char])
cmdStatus Text
"VOICE" Text
"+v") Bool -> ChannelCommand [Char]
simpleChannelTab
, NonEmpty Text
-> Args ArgsContext (Maybe [Char])
-> Text
-> CommandImpl (Maybe [Char])
-> Command
forall a.
NonEmpty Text
-> Args ArgsContext a -> Text -> CommandImpl a -> Command
Command
(Text -> NonEmpty Text
forall a. a -> NonEmpty a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
"devoice")
(Args ArgsContext [Char] -> Args ArgsContext (Maybe [Char])
forall r a. Args r a -> Args r (Maybe a)
optionalArg (Args ArgsContext [Char] -> Args ArgsContext (Maybe [Char]))
-> Args ArgsContext [Char] -> Args ArgsContext (Maybe [Char])
forall a b. (a -> b) -> a -> b
$ [Char] -> Args ArgsContext [Char]
forall r. [Char] -> Args r [Char]
simpleToken [Char]
"[nick]")
$(chanopDocs `cmdDoc` "devoice")
(CommandImpl (Maybe [Char]) -> Command)
-> CommandImpl (Maybe [Char]) -> Command
forall a b. (a -> b) -> a -> b
$ ChannelCommand (Maybe [Char])
-> (Bool -> ChannelCommand [Char]) -> CommandImpl (Maybe [Char])
forall a.
ChannelCommand a
-> (Bool -> ChannelCommand [Char]) -> CommandImpl a
ChannelCommand (Text -> Text -> ChannelCommand (Maybe [Char])
cmdStatus Text
"DEVOICE" Text
"-v") Bool -> ChannelCommand [Char]
simpleChannelTab
]
cmdRemove :: ChannelCommand (String, String)
cmdRemove :: ChannelCommand ([Char], [Char])
cmdRemove Identifier
channelId NetworkState
cs ClientState
st ([Char]
who,[Char]
reason) =
do let msg :: Text
msg = [Char] -> Text
Text.pack [Char]
reason
cmd :: RawIrcMsg
cmd = Identifier -> Text -> Text -> RawIrcMsg
ircRemove Identifier
channelId ([Char] -> Text
Text.pack [Char]
who) Text
msg
NetworkState
cs' <- Identifier -> [RawIrcMsg] -> NetworkState -> IO NetworkState
sendModeration Identifier
channelId [RawIrcMsg
cmd] NetworkState
cs
NetworkState -> ClientState -> IO CommandResult
commandSuccessUpdateCS NetworkState
cs' ClientState
st
cmdKick :: ChannelCommand (String, String)
cmdKick :: ChannelCommand ([Char], [Char])
cmdKick Identifier
channelId NetworkState
cs ClientState
st ([Char]
who,[Char]
reason) =
do let msg :: Text
msg = [Char] -> Text
Text.pack [Char]
reason
cmd :: RawIrcMsg
cmd = Identifier -> Text -> Text -> RawIrcMsg
ircKick Identifier
channelId ([Char] -> Text
Text.pack [Char]
who) Text
msg
NetworkState
cs' <- Identifier -> [RawIrcMsg] -> NetworkState -> IO NetworkState
sendModeration Identifier
channelId [RawIrcMsg
cmd] NetworkState
cs
NetworkState -> ClientState -> IO CommandResult
commandSuccessUpdateCS NetworkState
cs' ClientState
st
cmdKickBan :: ChannelCommand (String, String)
cmdKickBan :: ChannelCommand ([Char], [Char])
cmdKickBan Identifier
channelId NetworkState
cs ClientState
st ([Char]
who,[Char]
reason) =
do let msg :: Text
msg = [Char] -> Text
Text.pack [Char]
reason
whoTxt :: Text
whoTxt = [Char] -> Text
Text.pack [Char]
who
mask :: Text
mask = UserInfo -> Text
renderUserInfo (Identifier -> NetworkState -> UserInfo
computeBanUserInfo (Text -> Identifier
mkId Text
whoTxt) NetworkState
cs)
cmds :: [RawIrcMsg]
cmds = [ Identifier -> [Text] -> RawIrcMsg
ircMode Identifier
channelId [Text
"b", Text
mask]
, Identifier -> Text -> Text -> RawIrcMsg
ircKick Identifier
channelId Text
whoTxt Text
msg
]
NetworkState
cs' <- Identifier -> [RawIrcMsg] -> NetworkState -> IO NetworkState
sendModeration Identifier
channelId [RawIrcMsg]
cmds NetworkState
cs
NetworkState -> ClientState -> IO CommandResult
commandSuccessUpdateCS NetworkState
cs' ClientState
st
cmdQuiet :: ChannelCommand String
cmdQuiet :: ChannelCommand [Char]
cmdQuiet Identifier
channelId NetworkState
cs ClientState
st [Char]
who
| Char -> [Char] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem Char
'q' ([Char] -> Bool) -> [Char] -> Bool
forall a b. (a -> b) -> a -> b
$ Getting [Char] NetworkState [Char] -> NetworkState -> [Char]
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view ((ModeTypes -> Const [Char] ModeTypes)
-> NetworkState -> Const [Char] NetworkState
Lens' NetworkState ModeTypes
csModeTypes ((ModeTypes -> Const [Char] ModeTypes)
-> NetworkState -> Const [Char] NetworkState)
-> (([Char] -> Const [Char] [Char])
-> ModeTypes -> Const [Char] ModeTypes)
-> Getting [Char] NetworkState [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Char] -> Const [Char] [Char])
-> ModeTypes -> Const [Char] ModeTypes
forall (f :: * -> *).
Functor f =>
([Char] -> f [Char]) -> ModeTypes -> f ModeTypes
modesLists) NetworkState
cs = do
let
whoTxt :: Text
whoTxt = [Char] -> Text
Text.pack [Char]
who
mask :: Text
mask = if (Char -> Bool) -> Text -> Bool
Text.all Char -> Bool
isNickChar Text
whoTxt then UserInfo -> Text
renderUserInfo (Identifier -> NetworkState -> UserInfo
computeBanUserInfo (Text -> Identifier
mkId Text
whoTxt) NetworkState
cs) else Text
whoTxt
NetworkState
cs' <- Identifier -> [RawIrcMsg] -> NetworkState -> IO NetworkState
sendModeration Identifier
channelId [Identifier -> [Text] -> RawIrcMsg
ircMode Identifier
channelId [Text
"q", Text
mask]] NetworkState
cs
NetworkState -> ClientState -> IO CommandResult
commandSuccessUpdateCS NetworkState
cs' ClientState
st
| Bool
otherwise = Text -> ClientState -> IO CommandResult
commandFailureMsg Text
"no list mode q on network" ClientState
st
cmdInvite :: ChannelCommand String
cmdInvite :: ChannelCommand [Char]
cmdInvite Identifier
channelId NetworkState
cs ClientState
st [Char]
nick =
do let freeTarget :: Bool
freeTarget = Getting Any NetworkState Text -> NetworkState -> Bool
forall s a. Getting Any s a -> s -> Bool
has ((HashMap Identifier ChannelState
-> Const Any (HashMap Identifier ChannelState))
-> NetworkState -> Const Any NetworkState
Lens' NetworkState (HashMap Identifier ChannelState)
csChannels ((HashMap Identifier ChannelState
-> Const Any (HashMap Identifier ChannelState))
-> NetworkState -> Const Any NetworkState)
-> ((Text -> Const Any Text)
-> HashMap Identifier ChannelState
-> Const Any (HashMap Identifier ChannelState))
-> Getting Any NetworkState Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index (HashMap Identifier ChannelState)
-> Traversal'
(HashMap Identifier ChannelState)
(IxValue (HashMap Identifier ChannelState))
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Identifier
Index (HashMap Identifier ChannelState)
channelId ((ChannelState -> Const Any ChannelState)
-> HashMap Identifier ChannelState
-> Const Any (HashMap Identifier ChannelState))
-> ((Text -> Const Any Text)
-> ChannelState -> Const Any ChannelState)
-> (Text -> Const Any Text)
-> HashMap Identifier ChannelState
-> Const Any (HashMap Identifier ChannelState)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Map Char Text -> Const Any (Map Char Text))
-> ChannelState -> Const Any ChannelState
Lens' ChannelState (Map Char Text)
chanModes ((Map Char Text -> Const Any (Map Char Text))
-> ChannelState -> Const Any ChannelState)
-> ((Text -> Const Any Text)
-> Map Char Text -> Const Any (Map Char Text))
-> (Text -> Const Any Text)
-> ChannelState
-> Const Any ChannelState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index (Map Char Text)
-> Traversal' (Map Char Text) (IxValue (Map Char Text))
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Char
Index (Map Char Text)
'g') NetworkState
cs
cmd :: RawIrcMsg
cmd = Text -> Identifier -> RawIrcMsg
ircInvite ([Char] -> Text
Text.pack [Char]
nick) Identifier
channelId
NetworkState
cs' <- if Bool
freeTarget
then NetworkState
cs NetworkState -> IO () -> IO NetworkState
forall a b. a -> IO b -> IO a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ NetworkState -> RawIrcMsg -> IO ()
sendMsg NetworkState
cs RawIrcMsg
cmd
else Identifier -> [RawIrcMsg] -> NetworkState -> IO NetworkState
sendModeration Identifier
channelId [RawIrcMsg
cmd] NetworkState
cs
NetworkState -> ClientState -> IO CommandResult
commandSuccessUpdateCS NetworkState
cs' ClientState
st
cmdMasks :: ChannelCommand String
cmdMasks :: ChannelCommand [Char]
cmdMasks Identifier
channel NetworkState
cs ClientState
st [Char]
rest =
case [Char]
rest of
[Char
mode] | Char
mode Char -> [Char] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` Getting [Char] NetworkState [Char] -> NetworkState -> [Char]
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view ((ModeTypes -> Const [Char] ModeTypes)
-> NetworkState -> Const [Char] NetworkState
Lens' NetworkState ModeTypes
csModeTypes ((ModeTypes -> Const [Char] ModeTypes)
-> NetworkState -> Const [Char] NetworkState)
-> (([Char] -> Const [Char] [Char])
-> ModeTypes -> Const [Char] ModeTypes)
-> Getting [Char] NetworkState [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Char] -> Const [Char] [Char])
-> ModeTypes -> Const [Char] ModeTypes
forall (f :: * -> *).
Functor f =>
([Char] -> f [Char]) -> ModeTypes -> f ModeTypes
modesLists) NetworkState
cs ->
do let connecting :: Bool
connecting = Getting Any NetworkState (Int, Maybe UTCTime, ConnectRestriction)
-> NetworkState -> Bool
forall s a. Getting Any s a -> s -> Bool
has ((PingStatus -> Const Any PingStatus)
-> NetworkState -> Const Any NetworkState
Lens' NetworkState PingStatus
csPingStatus ((PingStatus -> Const Any PingStatus)
-> NetworkState -> Const Any NetworkState)
-> (((Int, Maybe UTCTime, ConnectRestriction)
-> Const Any (Int, Maybe UTCTime, ConnectRestriction))
-> PingStatus -> Const Any PingStatus)
-> Getting
Any NetworkState (Int, Maybe UTCTime, ConnectRestriction)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Int, Maybe UTCTime, ConnectRestriction)
-> Const Any (Int, Maybe UTCTime, ConnectRestriction))
-> PingStatus -> Const Any PingStatus
Prism' PingStatus (Int, Maybe UTCTime, ConnectRestriction)
_PingConnecting) NetworkState
cs
listLoaded :: Bool
listLoaded = Getting Any NetworkState (HashMap Text MaskListEntry)
-> NetworkState -> Bool
forall s a. Getting Any s a -> s -> Bool
has ((HashMap Identifier ChannelState
-> Const Any (HashMap Identifier ChannelState))
-> NetworkState -> Const Any NetworkState
Lens' NetworkState (HashMap Identifier ChannelState)
csChannels ((HashMap Identifier ChannelState
-> Const Any (HashMap Identifier ChannelState))
-> NetworkState -> Const Any NetworkState)
-> ((HashMap Text MaskListEntry
-> Const Any (HashMap Text MaskListEntry))
-> HashMap Identifier ChannelState
-> Const Any (HashMap Identifier ChannelState))
-> Getting Any NetworkState (HashMap Text MaskListEntry)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index (HashMap Identifier ChannelState)
-> Traversal'
(HashMap Identifier ChannelState)
(IxValue (HashMap Identifier ChannelState))
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Identifier
Index (HashMap Identifier ChannelState)
channel ((ChannelState -> Const Any ChannelState)
-> HashMap Identifier ChannelState
-> Const Any (HashMap Identifier ChannelState))
-> ((HashMap Text MaskListEntry
-> Const Any (HashMap Text MaskListEntry))
-> ChannelState -> Const Any ChannelState)
-> (HashMap Text MaskListEntry
-> Const Any (HashMap Text MaskListEntry))
-> HashMap Identifier ChannelState
-> Const Any (HashMap Identifier ChannelState)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Map Char (HashMap Text MaskListEntry)
-> Const Any (Map Char (HashMap Text MaskListEntry)))
-> ChannelState -> Const Any ChannelState
Lens' ChannelState (Map Char (HashMap Text MaskListEntry))
chanLists ((Map Char (HashMap Text MaskListEntry)
-> Const Any (Map Char (HashMap Text MaskListEntry)))
-> ChannelState -> Const Any ChannelState)
-> ((HashMap Text MaskListEntry
-> Const Any (HashMap Text MaskListEntry))
-> Map Char (HashMap Text MaskListEntry)
-> Const Any (Map Char (HashMap Text MaskListEntry)))
-> (HashMap Text MaskListEntry
-> Const Any (HashMap Text MaskListEntry))
-> ChannelState
-> Const Any ChannelState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index (Map Char (HashMap Text MaskListEntry))
-> Traversal'
(Map Char (HashMap Text MaskListEntry))
(IxValue (Map Char (HashMap Text MaskListEntry)))
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Char
Index (Map Char (HashMap Text MaskListEntry))
mode) NetworkState
cs
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Bool
connecting Bool -> Bool -> Bool
|| Bool
listLoaded)
(NetworkState -> RawIrcMsg -> IO ()
sendMsg NetworkState
cs (Identifier -> [Text] -> RawIrcMsg
ircMode Identifier
channel [Char -> Text
Text.singleton Char
mode]))
ClientState -> IO CommandResult
forall (m :: * -> *). Monad m => ClientState -> m CommandResult
commandSuccess (Subfocus -> ClientState -> ClientState
changeSubfocus (Text -> Identifier -> Char -> Subfocus
FocusMasks (Getting Text NetworkState Text -> NetworkState -> Text
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Text NetworkState Text
Lens' NetworkState Text
csNetwork NetworkState
cs) Identifier
channel Char
mode) ClientState
st)
[Char]
_ -> Text -> ClientState -> IO CommandResult
commandFailureMsg Text
"unknown mask mode" ClientState
st
cmdStatus :: Text -> Text -> ChannelCommand (Maybe String)
cmdStatus :: Text -> Text -> ChannelCommand (Maybe [Char])
cmdStatus Text
servCmd Text
modeChg Identifier
chan NetworkState
cs ClientState
st Maybe [Char]
target
| Identifier -> NetworkState -> Bool
useChanServ Identifier
chan NetworkState
cs = do
let command :: [Text]
command = [Text
servCmd, Identifier -> Text
idText Identifier
chan] [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ Maybe Text -> [Text]
forall a. Maybe a -> [a]
maybeToList Maybe Text
targetText
NetworkState -> RawIrcMsg -> IO ()
sendMsg NetworkState
cs (RawIrcMsg -> IO ()) -> RawIrcMsg -> IO ()
forall a b. (a -> b) -> a -> b
$ Text -> Text -> RawIrcMsg
ircPrivmsg Text
"ChanServ" (Text -> RawIrcMsg) -> Text -> RawIrcMsg
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
Text.unwords [Text]
command
NetworkState -> ClientState -> IO CommandResult
commandSuccessUpdateCS NetworkState
cs ClientState
st
| Bool
otherwise = do
let target' :: Text
target' = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe (Identifier -> Text
idText (Identifier -> Text) -> Identifier -> Text
forall a b. (a -> b) -> a -> b
$ Getting Identifier NetworkState Identifier
-> NetworkState -> Identifier
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Identifier NetworkState Identifier
Lens' NetworkState Identifier
csNick NetworkState
cs) Maybe Text
targetText
NetworkState -> RawIrcMsg -> IO ()
sendMsg NetworkState
cs (RawIrcMsg -> IO ()) -> RawIrcMsg -> IO ()
forall a b. (a -> b) -> a -> b
$ Identifier -> [Text] -> RawIrcMsg
ircMode Identifier
chan [Text
modeChg, Text
target']
NetworkState -> ClientState -> IO CommandResult
commandSuccessUpdateCS NetworkState
cs ClientState
st
where
targetText :: Maybe Text
targetText = [Char] -> Text
Text.pack ([Char] -> Text) -> Maybe [Char] -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe [Char]
target
computeBanUserInfo :: Identifier -> NetworkState -> UserInfo
computeBanUserInfo :: Identifier -> NetworkState -> UserInfo
computeBanUserInfo Identifier
who NetworkState
cs =
case Getting (Maybe UserAndHost) NetworkState (Maybe UserAndHost)
-> NetworkState -> Maybe UserAndHost
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view (Identifier
-> Getting (Maybe UserAndHost) NetworkState (Maybe UserAndHost)
forall (f :: * -> *).
Functor f =>
Identifier -> LensLike' f NetworkState (Maybe UserAndHost)
csUser Identifier
who) NetworkState
cs of
Maybe UserAndHost
Nothing -> Identifier -> Text -> Text -> UserInfo
UserInfo Identifier
who Text
"*" Text
"*"
Just (UserAndHost Text
_ Text
host Text
_) -> Identifier -> Text -> Text -> UserInfo
UserInfo Identifier
"*" Text
"*" Text
host
cmdTopic :: ChannelCommand String
cmdTopic :: ChannelCommand [Char]
cmdTopic Identifier
channelId NetworkState
cs ClientState
st [Char]
rest =
do Identifier -> Text -> NetworkState -> IO ()
sendTopic Identifier
channelId ([Char] -> Text
Text.pack [Char]
rest) NetworkState
cs
ClientState -> IO CommandResult
forall (m :: * -> *). Monad m => ClientState -> m CommandResult
commandSuccess ClientState
st
tabTopic ::
Bool ->
ChannelCommand String
tabTopic :: Bool -> ChannelCommand [Char]
tabTopic Bool
_ Identifier
channelId NetworkState
cs ClientState
st [Char]
rest
| (Char -> Bool) -> [Char] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==Char
' ') [Char]
rest
, Just Text
topic <- Getting (First Text) NetworkState Text
-> NetworkState -> Maybe Text
forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview ((HashMap Identifier ChannelState
-> Const (First Text) (HashMap Identifier ChannelState))
-> NetworkState -> Const (First Text) NetworkState
Lens' NetworkState (HashMap Identifier ChannelState)
csChannels ((HashMap Identifier ChannelState
-> Const (First Text) (HashMap Identifier ChannelState))
-> NetworkState -> Const (First Text) NetworkState)
-> ((Text -> Const (First Text) Text)
-> HashMap Identifier ChannelState
-> Const (First Text) (HashMap Identifier ChannelState))
-> Getting (First Text) NetworkState Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index (HashMap Identifier ChannelState)
-> Traversal'
(HashMap Identifier ChannelState)
(IxValue (HashMap Identifier ChannelState))
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Identifier
Index (HashMap Identifier ChannelState)
channelId ((ChannelState -> Const (First Text) ChannelState)
-> HashMap Identifier ChannelState
-> Const (First Text) (HashMap Identifier ChannelState))
-> ((Text -> Const (First Text) Text)
-> ChannelState -> Const (First Text) ChannelState)
-> (Text -> Const (First Text) Text)
-> HashMap Identifier ChannelState
-> Const (First Text) (HashMap Identifier ChannelState)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Const (First Text) Text)
-> ChannelState -> Const (First Text) ChannelState
Lens' ChannelState Text
chanTopic) NetworkState
cs =
do let textBox :: EditBox -> EditBox
textBox = ASetter EditBox EditBox Line Line -> Line -> EditBox -> EditBox
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter EditBox EditBox Line Line
forall c. HasLine c => Lens' c Line
Lens' EditBox Line
Edit.line ([Char] -> Line
Edit.endLine ([Char] -> Line) -> [Char] -> Line
forall a b. (a -> b) -> a -> b
$ [Char]
"/topic " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Text -> [Char]
Text.unpack Text
topic)
ClientState -> IO CommandResult
forall (m :: * -> *). Monad m => ClientState -> m CommandResult
commandSuccess (ASetter ClientState ClientState EditBox EditBox
-> (EditBox -> EditBox) -> ClientState -> ClientState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter ClientState ClientState EditBox EditBox
Lens' ClientState EditBox
clientTextBox EditBox -> EditBox
textBox ClientState
st)
| Bool
otherwise = ClientState -> IO CommandResult
forall (m :: * -> *). Monad m => ClientState -> m CommandResult
commandFailure ClientState
st
cmdMode :: MaybeChatCommand [String]
cmdMode :: MaybeChatCommand [[Char]]
cmdMode Maybe Identifier
chan NetworkState
cs ClientState
st [[Char]]
xs = Maybe Identifier
-> [Text] -> NetworkState -> ClientState -> IO CommandResult
modeCommand Maybe Identifier
chan ([Char] -> Text
Text.pack ([Char] -> Text) -> [[Char]] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [[Char]]
xs) NetworkState
cs ClientState
st
modeCommand ::
Maybe Identifier ->
[Text] ->
NetworkState ->
ClientState ->
IO CommandResult
modeCommand :: Maybe Identifier
-> [Text] -> NetworkState -> ClientState -> IO CommandResult
modeCommand Maybe Identifier
maybeChan [Text]
modes NetworkState
cs ClientState
st =
case Maybe Identifier
maybeChan of
Maybe Identifier
Nothing ->
do NetworkState -> RawIrcMsg -> IO ()
sendMsg NetworkState
cs (Identifier -> [Text] -> RawIrcMsg
ircMode (Getting Identifier NetworkState Identifier
-> NetworkState -> Identifier
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Identifier NetworkState Identifier
Lens' NetworkState Identifier
csNick NetworkState
cs) [Text]
modes)
ClientState -> IO CommandResult
forall (m :: * -> *). Monad m => ClientState -> m CommandResult
commandSuccess ClientState
st
Just Identifier
chan ->
case [Text]
modes of
[] -> Bool -> [[Text]] -> IO CommandResult
success Bool
False [[]]
Text
flags:[Text]
params ->
case ModeTypes -> Text -> [Text] -> Maybe [(Bool, Char, Text)]
splitModes (Getting ModeTypes NetworkState ModeTypes
-> NetworkState -> ModeTypes
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting ModeTypes NetworkState ModeTypes
Lens' NetworkState ModeTypes
csModeTypes NetworkState
cs) Text
flags [Text]
params of
Maybe [(Bool, Char, Text)]
Nothing -> Text -> ClientState -> IO CommandResult
commandFailureMsg Text
"failed to parse modes" ClientState
st
Just [(Bool, Char, Text)]
parsedModes ->
Bool -> [[Text]] -> IO CommandResult
success Bool
needOp ([(Bool, Char, Text)] -> [Text]
unsplitModes ([(Bool, Char, Text)] -> [Text])
-> [[(Bool, Char, Text)]] -> [[Text]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> [(Bool, Char, Text)] -> [[(Bool, Char, Text)]]
forall e. Int -> [e] -> [[e]]
chunksOf (Getting Int NetworkState Int -> NetworkState -> Int
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Int NetworkState Int
Lens' NetworkState Int
csModeCount NetworkState
cs) [(Bool, Char, Text)]
parsedModes')
where
parsedModes' :: [(Bool, Char, Text)]
parsedModes'
| Identifier -> NetworkState -> Bool
useChanServ Identifier
chan NetworkState
cs = ((Bool, Char, Text) -> Bool)
-> [(Bool, Char, Text)] -> [(Bool, Char, Text)]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool)
-> ((Bool, Char, Text) -> Bool) -> (Bool, Char, Text) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Bool, Char, Text) -> Bool
isOpMe) [(Bool, Char, Text)]
parsedModes
| Bool
otherwise = [(Bool, Char, Text)]
parsedModes
needOp :: Bool
needOp = Bool -> Bool
not (((Bool, Char, Text) -> Bool) -> [(Bool, Char, Text)] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Bool, Char, Text) -> Bool
isPublicChannelMode [(Bool, Char, Text)]
parsedModes)
where
isOpMe :: (Bool, Char, Text) -> Bool
isOpMe (Bool
True, Char
'o', Text
param) = Text -> Identifier
mkId Text
param Identifier -> Identifier -> Bool
forall a. Eq a => a -> a -> Bool
== Getting Identifier NetworkState Identifier
-> NetworkState -> Identifier
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Identifier NetworkState Identifier
Lens' NetworkState Identifier
csNick NetworkState
cs
isOpMe (Bool, Char, Text)
_ = Bool
False
success :: Bool -> [[Text]] -> IO CommandResult
success Bool
needOp [[Text]]
argss =
do let cmds :: [RawIrcMsg]
cmds = Identifier -> [Text] -> RawIrcMsg
ircMode Identifier
chan ([Text] -> RawIrcMsg) -> [[Text]] -> [RawIrcMsg]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [[Text]]
argss
NetworkState
cs' <- if Bool
needOp
then Identifier -> [RawIrcMsg] -> NetworkState -> IO NetworkState
sendModeration Identifier
chan [RawIrcMsg]
cmds NetworkState
cs
else NetworkState
cs NetworkState -> IO () -> IO NetworkState
forall a b. a -> IO b -> IO a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (RawIrcMsg -> IO ()) -> [RawIrcMsg] -> IO ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ (NetworkState -> RawIrcMsg -> IO ()
sendMsg NetworkState
cs) [RawIrcMsg]
cmds
NetworkState -> ClientState -> IO CommandResult
commandSuccessUpdateCS NetworkState
cs' ClientState
st
tabMode :: Bool -> MaybeChatCommand String
tabMode :: Bool -> MaybeChatCommand [Char]
tabMode Bool
isReversed Maybe Identifier
maybeChan NetworkState
cs ClientState
st [Char]
rest =
case Maybe Identifier
maybeChan of
Just Identifier
channel
| Text
flags:[Text]
params <- Text -> [Text]
Text.words ([Char] -> Text
Text.pack [Char]
rest)
, Just [(Bool, Char, Text)]
parsedModes <- ModeTypes -> Text -> [Text] -> Maybe [(Bool, Char, Text)]
splitModes (Getting ModeTypes NetworkState ModeTypes
-> NetworkState -> ModeTypes
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting ModeTypes NetworkState ModeTypes
Lens' NetworkState ModeTypes
csModeTypes NetworkState
cs) Text
flags [Text]
params
, let parsedModesWithParams :: [(Bool, Char)]
parsedModesWithParams =
[ (Bool
pol,Char
mode) | (Bool
pol,Char
mode,Text
arg) <- [(Bool, Char, Text)]
parsedModes, Bool -> Bool
not (Text -> Bool
Text.null Text
arg) ]
, (Bool
pol,Char
mode):[(Bool, Char)]
_ <- Int -> [(Bool, Char)] -> [(Bool, Char)]
forall a. Int -> [a] -> [a]
drop (Int
paramIndexInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
3) [(Bool, Char)]
parsedModesWithParams
, let ([Identifier]
hint, [Identifier]
completions) = Bool
-> Char
-> Identifier
-> NetworkState
-> ClientState
-> ([Identifier], [Identifier])
computeModeCompletion Bool
pol Char
mode Identifier
channel NetworkState
cs ClientState
st
-> WordCompletionMode
-> [Identifier]
-> [Identifier]
-> Bool
-> ClientState
-> IO CommandResult
forall a.
Prefix a =>
WordCompletionMode
-> [a] -> [a] -> Bool -> ClientState -> IO CommandResult
simpleTabCompletion WordCompletionMode
plainWordCompleteMode [Identifier]
hint [Identifier]
completions Bool
isReversed ClientState
st
Maybe Identifier
_ -> ClientState -> IO CommandResult
forall (m :: * -> *). Monad m => ClientState -> m CommandResult
commandFailure ClientState
st
where
paramIndex :: Int
paramIndex = [[Char]] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([[Char]] -> Int) -> [[Char]] -> Int
forall a b. (a -> b) -> a -> b
$ [Char] -> [[Char]]
words ([Char] -> [[Char]]) -> [Char] -> [[Char]]
forall a b. (a -> b) -> a -> b
$ (Int -> [Char] -> [Char]) -> (Int, [Char]) -> [Char]
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Int -> [Char] -> [Char]
forall a. Int -> [a] -> [a]
take ((Int, [Char]) -> [Char]) -> (Int, [Char]) -> [Char]
forall a b. (a -> b) -> a -> b
$ ClientState -> (Int, [Char])
clientLine ClientState
st
modeParamArgs :: ArgsContext -> String -> Maybe (Args ArgsContext [String])
modeParamArgs :: ArgsContext -> [Char] -> Maybe (Args ArgsContext [[Char]])
modeParamArgs ArgsContext{argsContextSt :: ArgsContext -> ClientState
argsContextSt=ClientState
st, argsContextFocus :: ArgsContext -> Focus
argsContextFocus=Focus
focus} [Char]
str =
case Focus
focus of
Focus
Unfocused -> Maybe (Args ArgsContext [[Char]])
forall a. Maybe a
Nothing
NetworkFocus Text
_ -> Args ArgsContext [[Char]] -> Maybe (Args ArgsContext [[Char]])
forall a. a -> Maybe a
Just ([[Char]] -> Args ArgsContext [[Char]]
forall a. a -> Ap (Arg ArgsContext) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure [[Char]
str])
ChannelFocus Text
net Identifier
_ ->
do NetworkState
cs <- Getting (First NetworkState) ClientState NetworkState
-> ClientState -> Maybe NetworkState
forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview (Text -> Getting (First NetworkState) ClientState NetworkState
forall (f :: * -> *).
Applicative f =>
Text -> LensLike' f ClientState NetworkState
clientConnection Text
net) ClientState
st
let types :: ModeTypes
types = Getting ModeTypes NetworkState ModeTypes
-> NetworkState -> ModeTypes
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting ModeTypes NetworkState ModeTypes
Lens' NetworkState ModeTypes
csModeTypes NetworkState
cs
[(Bool, Char, Text)]
flags <- ModeTypes -> Text -> [Text] -> Maybe [(Bool, Char, Text)]
splitModes ModeTypes
types ([Char] -> Text
Text.pack [Char]
str) []
let ([[Char]]
req,[[Char]]
opt) = ((Bool, Char, Text)
-> ([[Char]], [[Char]]) -> ([[Char]], [[Char]]))
-> ([[Char]], [[Char]])
-> [(Bool, Char, Text)]
-> ([[Char]], [[Char]])
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (ModeTypes
-> (Bool, Char, Text)
-> ([[Char]], [[Char]])
-> ([[Char]], [[Char]])
countFlags ModeTypes
types) ([],[]) [(Bool, Char, Text)]
flags
Args ArgsContext [[Char]] -> Maybe (Args ArgsContext [[Char]])
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return (([Char]
str[Char] -> [[Char]] -> [[Char]]
forall a. a -> [a] -> [a]
:) ([[Char]] -> [[Char]])
-> Args ArgsContext [[Char]] -> Args ArgsContext [[Char]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [[Char]] -> [[Char]] -> Args ArgsContext [[Char]]
forall r. [[Char]] -> [[Char]] -> Args r [[Char]]
tokenList [[Char]]
req (([Char] -> [Char]) -> [[Char]] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map ([Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++[Char]
"?") [[Char]]
opt))
countFlags ::
ModeTypes ->
(Bool, Char, Text) ->
([String],[String]) ->
([String],[String])
countFlags :: ModeTypes
-> (Bool, Char, Text)
-> ([[Char]], [[Char]])
-> ([[Char]], [[Char]])
countFlags ModeTypes
types (Bool
pol, Char
flag, Text
_)
| Char
flag Char -> [Char] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (([Char] -> Const [Char] [Char])
-> ModeTypes -> Const [Char] ModeTypes)
-> ModeTypes -> [Char]
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view ([Char] -> Const [Char] [Char])
-> ModeTypes -> Const [Char] ModeTypes
forall (f :: * -> *).
Functor f =>
([Char] -> f [Char]) -> ModeTypes -> f ModeTypes
modesLists ModeTypes
types = ([[Char]], [[Char]]) -> ([[Char]], [[Char]])
addOpt
| Bool
pol Bool -> Bool -> Bool
&& Char
flag Char -> [Char] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (([Char] -> Const [Char] [Char])
-> ModeTypes -> Const [Char] ModeTypes)
-> ModeTypes -> [Char]
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view ([Char] -> Const [Char] [Char])
-> ModeTypes -> Const [Char] ModeTypes
forall (f :: * -> *).
Functor f =>
([Char] -> f [Char]) -> ModeTypes -> f ModeTypes
modesSetArg ModeTypes
types = ([[Char]], [[Char]]) -> ([[Char]], [[Char]])
forall {b}. ([[Char]], b) -> ([[Char]], b)
addReq
| Char
flag Char -> [Char] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (([Char] -> Const [Char] [Char])
-> ModeTypes -> Const [Char] ModeTypes)
-> ModeTypes -> [Char]
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view ([Char] -> Const [Char] [Char])
-> ModeTypes -> Const [Char] ModeTypes
forall (f :: * -> *).
Functor f =>
([Char] -> f [Char]) -> ModeTypes -> f ModeTypes
modesAlwaysArg ModeTypes
types = ([[Char]], [[Char]]) -> ([[Char]], [[Char]])
forall {b}. ([[Char]], b) -> ([[Char]], b)
addReq
| Getting Any ModeTypes Char -> Char -> ModeTypes -> Bool
forall a s. Eq a => Getting Any s a -> a -> s -> Bool
elemOf (([(Char, Char)] -> Const Any [(Char, Char)])
-> ModeTypes -> Const Any ModeTypes
forall (f :: * -> *).
Functor f =>
([(Char, Char)] -> f [(Char, Char)]) -> ModeTypes -> f ModeTypes
modesPrefixModes (([(Char, Char)] -> Const Any [(Char, Char)])
-> ModeTypes -> Const Any ModeTypes)
-> ((Char -> Const Any Char)
-> [(Char, Char)] -> Const Any [(Char, Char)])
-> Getting Any ModeTypes Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Char, Char) -> Const Any (Char, Char))
-> [(Char, Char)] -> Const Any [(Char, Char)]
forall (f :: * -> *) a. Foldable f => IndexedFold Int (f a) a
IndexedFold Int [(Char, Char)] (Char, Char)
folded (((Char, Char) -> Const Any (Char, Char))
-> [(Char, Char)] -> Const Any [(Char, Char)])
-> ((Char -> Const Any Char)
-> (Char, Char) -> Const Any (Char, Char))
-> (Char -> Const Any Char)
-> [(Char, Char)]
-> Const Any [(Char, Char)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Const Any Char) -> (Char, Char) -> Const Any (Char, Char)
forall s t a b. Field1 s t a b => Lens s t a b
Lens (Char, Char) (Char, Char) Char Char
_1) Char
flag ModeTypes
types = ([[Char]], [[Char]]) -> ([[Char]], [[Char]])
forall {b}. ([[Char]], b) -> ([[Char]], b)
addReq
| Bool
otherwise = ([[Char]], [[Char]]) -> ([[Char]], [[Char]])
forall a. a -> a
id
where
addReq :: ([[Char]], b) -> ([[Char]], b)
addReq ([[Char]]
req,b
opt) = ((Char
flagChar -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:[Char]
" param")[Char] -> [[Char]] -> [[Char]]
forall a. a -> [a] -> [a]
:[[Char]]
req,b
opt)
addOpt :: ([[Char]], [[Char]]) -> ([[Char]], [[Char]])
addOpt ([] ,[[Char]]
opt) = ([], (Char
flagChar -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:[Char]
" param")[Char] -> [[Char]] -> [[Char]]
forall a. a -> [a] -> [a]
:[[Char]]
opt)
addOpt ([[Char]]
req,[[Char]]
opt) = ((Char
flagChar -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:[Char]
" param")[Char] -> [[Char]] -> [[Char]]
forall a. a -> [a] -> [a]
:[[Char]]
req,[[Char]]
opt)
computeModeCompletion ::
Bool ->
Char ->
Identifier ->
NetworkState ->
ClientState ->
([Identifier],[Identifier])
computeModeCompletion :: Bool
-> Char
-> Identifier
-> NetworkState
-> ClientState
-> ([Identifier], [Identifier])
computeModeCompletion Bool
pol Char
mode Identifier
channel NetworkState
cs ClientState
st
| Char
mode Char -> [Char] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (([Char] -> Const [Char] [Char])
-> ModeTypes -> Const [Char] ModeTypes)
-> ModeTypes -> [Char]
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view ([Char] -> Const [Char] [Char])
-> ModeTypes -> Const [Char] ModeTypes
forall (f :: * -> *).
Functor f =>
([Char] -> f [Char]) -> ModeTypes -> f ModeTypes
modesLists ModeTypes
modeSettings =
if Bool
pol then ([],[Identifier]
usermasks [Identifier] -> [Identifier] -> [Identifier]
forall a. Semigroup a => a -> a -> a
<> [Identifier]
accounts) else ([],[Identifier]
masks)
| Bool
otherwise = (ClientState -> [Identifier]
activeNicks ClientState
st, [Identifier]
nicks)
where
modeSettings :: ModeTypes
modeSettings = Getting ModeTypes NetworkState ModeTypes
-> NetworkState -> ModeTypes
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting ModeTypes NetworkState ModeTypes
Lens' NetworkState ModeTypes
csModeTypes NetworkState
cs
nicks :: [Identifier]
nicks = HashMap Identifier [Char] -> [Identifier]
forall k v. HashMap k v -> [k]
HashMap.keys (Getting
(HashMap Identifier [Char])
NetworkState
(HashMap Identifier [Char])
-> NetworkState -> HashMap Identifier [Char]
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view ((HashMap Identifier ChannelState
-> Const
(HashMap Identifier [Char]) (HashMap Identifier ChannelState))
-> NetworkState -> Const (HashMap Identifier [Char]) NetworkState
Lens' NetworkState (HashMap Identifier ChannelState)
csChannels ((HashMap Identifier ChannelState
-> Const
(HashMap Identifier [Char]) (HashMap Identifier ChannelState))
-> NetworkState -> Const (HashMap Identifier [Char]) NetworkState)
-> ((HashMap Identifier [Char]
-> Const (HashMap Identifier [Char]) (HashMap Identifier [Char]))
-> HashMap Identifier ChannelState
-> Const
(HashMap Identifier [Char]) (HashMap Identifier ChannelState))
-> Getting
(HashMap Identifier [Char])
NetworkState
(HashMap Identifier [Char])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index (HashMap Identifier ChannelState)
-> Traversal'
(HashMap Identifier ChannelState)
(IxValue (HashMap Identifier ChannelState))
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Identifier
Index (HashMap Identifier ChannelState)
channel ((ChannelState -> Const (HashMap Identifier [Char]) ChannelState)
-> HashMap Identifier ChannelState
-> Const
(HashMap Identifier [Char]) (HashMap Identifier ChannelState))
-> ((HashMap Identifier [Char]
-> Const (HashMap Identifier [Char]) (HashMap Identifier [Char]))
-> ChannelState -> Const (HashMap Identifier [Char]) ChannelState)
-> (HashMap Identifier [Char]
-> Const (HashMap Identifier [Char]) (HashMap Identifier [Char]))
-> HashMap Identifier ChannelState
-> Const
(HashMap Identifier [Char]) (HashMap Identifier ChannelState)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (HashMap Identifier [Char]
-> Const (HashMap Identifier [Char]) (HashMap Identifier [Char]))
-> ChannelState -> Const (HashMap Identifier [Char]) ChannelState
Lens' ChannelState (HashMap Identifier [Char])
chanUsers) NetworkState
cs)
masks :: [Identifier]
masks = Text -> Identifier
mkId (Text -> Identifier) -> [Text] -> [Identifier]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> HashMap Text MaskListEntry -> [Text]
forall k v. HashMap k v -> [k]
HashMap.keys (Getting
(HashMap Text MaskListEntry)
NetworkState
(HashMap Text MaskListEntry)
-> NetworkState -> HashMap Text MaskListEntry
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view ((HashMap Identifier ChannelState
-> Const
(HashMap Text MaskListEntry) (HashMap Identifier ChannelState))
-> NetworkState -> Const (HashMap Text MaskListEntry) NetworkState
Lens' NetworkState (HashMap Identifier ChannelState)
csChannels ((HashMap Identifier ChannelState
-> Const
(HashMap Text MaskListEntry) (HashMap Identifier ChannelState))
-> NetworkState -> Const (HashMap Text MaskListEntry) NetworkState)
-> ((HashMap Text MaskListEntry
-> Const (HashMap Text MaskListEntry) (HashMap Text MaskListEntry))
-> HashMap Identifier ChannelState
-> Const
(HashMap Text MaskListEntry) (HashMap Identifier ChannelState))
-> Getting
(HashMap Text MaskListEntry)
NetworkState
(HashMap Text MaskListEntry)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index (HashMap Identifier ChannelState)
-> Traversal'
(HashMap Identifier ChannelState)
(IxValue (HashMap Identifier ChannelState))
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Identifier
Index (HashMap Identifier ChannelState)
channel ((ChannelState -> Const (HashMap Text MaskListEntry) ChannelState)
-> HashMap Identifier ChannelState
-> Const
(HashMap Text MaskListEntry) (HashMap Identifier ChannelState))
-> ((HashMap Text MaskListEntry
-> Const (HashMap Text MaskListEntry) (HashMap Text MaskListEntry))
-> ChannelState -> Const (HashMap Text MaskListEntry) ChannelState)
-> (HashMap Text MaskListEntry
-> Const (HashMap Text MaskListEntry) (HashMap Text MaskListEntry))
-> HashMap Identifier ChannelState
-> Const
(HashMap Text MaskListEntry) (HashMap Identifier ChannelState)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Map Char (HashMap Text MaskListEntry)
-> Const
(HashMap Text MaskListEntry)
(Map Char (HashMap Text MaskListEntry)))
-> ChannelState -> Const (HashMap Text MaskListEntry) ChannelState
Lens' ChannelState (Map Char (HashMap Text MaskListEntry))
chanLists ((Map Char (HashMap Text MaskListEntry)
-> Const
(HashMap Text MaskListEntry)
(Map Char (HashMap Text MaskListEntry)))
-> ChannelState -> Const (HashMap Text MaskListEntry) ChannelState)
-> ((HashMap Text MaskListEntry
-> Const (HashMap Text MaskListEntry) (HashMap Text MaskListEntry))
-> Map Char (HashMap Text MaskListEntry)
-> Const
(HashMap Text MaskListEntry)
(Map Char (HashMap Text MaskListEntry)))
-> (HashMap Text MaskListEntry
-> Const (HashMap Text MaskListEntry) (HashMap Text MaskListEntry))
-> ChannelState
-> Const (HashMap Text MaskListEntry) ChannelState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index (Map Char (HashMap Text MaskListEntry))
-> Traversal'
(Map Char (HashMap Text MaskListEntry))
(IxValue (Map Char (HashMap Text MaskListEntry)))
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Char
Index (Map Char (HashMap Text MaskListEntry))
mode) NetworkState
cs)
usermasks :: [Identifier]
usermasks =
[ Text -> Identifier
mkId (Text
"*!*@" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
host)
| Identifier
nick <- HashMap Identifier [Char] -> [Identifier]
forall k v. HashMap k v -> [k]
HashMap.keys (Getting
(HashMap Identifier [Char])
NetworkState
(HashMap Identifier [Char])
-> NetworkState -> HashMap Identifier [Char]
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view ((HashMap Identifier ChannelState
-> Const
(HashMap Identifier [Char]) (HashMap Identifier ChannelState))
-> NetworkState -> Const (HashMap Identifier [Char]) NetworkState
Lens' NetworkState (HashMap Identifier ChannelState)
csChannels ((HashMap Identifier ChannelState
-> Const
(HashMap Identifier [Char]) (HashMap Identifier ChannelState))
-> NetworkState -> Const (HashMap Identifier [Char]) NetworkState)
-> ((HashMap Identifier [Char]
-> Const (HashMap Identifier [Char]) (HashMap Identifier [Char]))
-> HashMap Identifier ChannelState
-> Const
(HashMap Identifier [Char]) (HashMap Identifier ChannelState))
-> Getting
(HashMap Identifier [Char])
NetworkState
(HashMap Identifier [Char])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index (HashMap Identifier ChannelState)
-> Traversal'
(HashMap Identifier ChannelState)
(IxValue (HashMap Identifier ChannelState))
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Identifier
Index (HashMap Identifier ChannelState)
channel ((ChannelState -> Const (HashMap Identifier [Char]) ChannelState)
-> HashMap Identifier ChannelState
-> Const
(HashMap Identifier [Char]) (HashMap Identifier ChannelState))
-> ((HashMap Identifier [Char]
-> Const (HashMap Identifier [Char]) (HashMap Identifier [Char]))
-> ChannelState -> Const (HashMap Identifier [Char]) ChannelState)
-> (HashMap Identifier [Char]
-> Const (HashMap Identifier [Char]) (HashMap Identifier [Char]))
-> HashMap Identifier ChannelState
-> Const
(HashMap Identifier [Char]) (HashMap Identifier ChannelState)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (HashMap Identifier [Char]
-> Const (HashMap Identifier [Char]) (HashMap Identifier [Char]))
-> ChannelState -> Const (HashMap Identifier [Char]) ChannelState
Lens' ChannelState (HashMap Identifier [Char])
chanUsers) NetworkState
cs)
, UserAndHost Text
_ Text
host Text
_ <- Getting (Endo [UserAndHost]) NetworkState UserAndHost
-> NetworkState -> [UserAndHost]
forall a s. Getting (Endo [a]) s a -> s -> [a]
toListOf ((HashMap Identifier UserAndHost
-> Const (Endo [UserAndHost]) (HashMap Identifier UserAndHost))
-> NetworkState -> Const (Endo [UserAndHost]) NetworkState
Lens' NetworkState (HashMap Identifier UserAndHost)
csUsers ((HashMap Identifier UserAndHost
-> Const (Endo [UserAndHost]) (HashMap Identifier UserAndHost))
-> NetworkState -> Const (Endo [UserAndHost]) NetworkState)
-> ((UserAndHost -> Const (Endo [UserAndHost]) UserAndHost)
-> HashMap Identifier UserAndHost
-> Const (Endo [UserAndHost]) (HashMap Identifier UserAndHost))
-> Getting (Endo [UserAndHost]) NetworkState UserAndHost
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index (HashMap Identifier UserAndHost)
-> Traversal'
(HashMap Identifier UserAndHost)
(IxValue (HashMap Identifier UserAndHost))
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Identifier
Index (HashMap Identifier UserAndHost)
nick) NetworkState
cs
]
accounts :: [Identifier]
accounts =
[ Text -> Identifier
mkId (Text
"$a:" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
account)
| Identifier
nick <- HashMap Identifier [Char] -> [Identifier]
forall k v. HashMap k v -> [k]
HashMap.keys (Getting
(HashMap Identifier [Char])
NetworkState
(HashMap Identifier [Char])
-> NetworkState -> HashMap Identifier [Char]
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view ((HashMap Identifier ChannelState
-> Const
(HashMap Identifier [Char]) (HashMap Identifier ChannelState))
-> NetworkState -> Const (HashMap Identifier [Char]) NetworkState
Lens' NetworkState (HashMap Identifier ChannelState)
csChannels ((HashMap Identifier ChannelState
-> Const
(HashMap Identifier [Char]) (HashMap Identifier ChannelState))
-> NetworkState -> Const (HashMap Identifier [Char]) NetworkState)
-> ((HashMap Identifier [Char]
-> Const (HashMap Identifier [Char]) (HashMap Identifier [Char]))
-> HashMap Identifier ChannelState
-> Const
(HashMap Identifier [Char]) (HashMap Identifier ChannelState))
-> Getting
(HashMap Identifier [Char])
NetworkState
(HashMap Identifier [Char])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index (HashMap Identifier ChannelState)
-> Traversal'
(HashMap Identifier ChannelState)
(IxValue (HashMap Identifier ChannelState))
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Identifier
Index (HashMap Identifier ChannelState)
channel ((ChannelState -> Const (HashMap Identifier [Char]) ChannelState)
-> HashMap Identifier ChannelState
-> Const
(HashMap Identifier [Char]) (HashMap Identifier ChannelState))
-> ((HashMap Identifier [Char]
-> Const (HashMap Identifier [Char]) (HashMap Identifier [Char]))
-> ChannelState -> Const (HashMap Identifier [Char]) ChannelState)
-> (HashMap Identifier [Char]
-> Const (HashMap Identifier [Char]) (HashMap Identifier [Char]))
-> HashMap Identifier ChannelState
-> Const
(HashMap Identifier [Char]) (HashMap Identifier ChannelState)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (HashMap Identifier [Char]
-> Const (HashMap Identifier [Char]) (HashMap Identifier [Char]))
-> ChannelState -> Const (HashMap Identifier [Char]) ChannelState
Lens' ChannelState (HashMap Identifier [Char])
chanUsers) NetworkState
cs)
, UserAndHost Text
_ Text
_ Text
account <- Getting (Endo [UserAndHost]) NetworkState UserAndHost
-> NetworkState -> [UserAndHost]
forall a s. Getting (Endo [a]) s a -> s -> [a]
toListOf ((HashMap Identifier UserAndHost
-> Const (Endo [UserAndHost]) (HashMap Identifier UserAndHost))
-> NetworkState -> Const (Endo [UserAndHost]) NetworkState
Lens' NetworkState (HashMap Identifier UserAndHost)
csUsers ((HashMap Identifier UserAndHost
-> Const (Endo [UserAndHost]) (HashMap Identifier UserAndHost))
-> NetworkState -> Const (Endo [UserAndHost]) NetworkState)
-> ((UserAndHost -> Const (Endo [UserAndHost]) UserAndHost)
-> HashMap Identifier UserAndHost
-> Const (Endo [UserAndHost]) (HashMap Identifier UserAndHost))
-> Getting (Endo [UserAndHost]) NetworkState UserAndHost
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index (HashMap Identifier UserAndHost)
-> Traversal'
(HashMap Identifier UserAndHost)
(IxValue (HashMap Identifier UserAndHost))
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Identifier
Index (HashMap Identifier UserAndHost)
nick) NetworkState
cs
, Bool -> Bool
not (Text -> Bool
Text.null Text
account)
]
isPublicChannelMode :: (Bool, Char, Text) -> Bool
isPublicChannelMode :: (Bool, Char, Text) -> Bool
isPublicChannelMode (Bool
True, Char
'b', Text
param) = Text -> Bool
Text.null Text
param
isPublicChannelMode (Bool
True, Char
'q', Text
param) = Text -> Bool
Text.null Text
param
isPublicChannelMode (Bool, Char, Text)
_ = Bool
False