{-# Language OverloadedStrings, TemplateHaskell #-}
{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE ViewPatterns #-}
module Client.Commands.Queries (queryCommands) where
import Client.Commands.Arguments.Spec (optionalArg, remainingArg, simpleToken, tokenArg)
import Client.Commands.Docs (queriesDocs, cmdDoc)
import Client.Commands.TabCompletion (noNetworkTab, simpleNetworkTab)
import Client.Commands.Types (commandSuccess, commandSuccessUpdateCS, Command(Command), CommandImpl(NetworkCommand), CommandSection(CommandSection), NetworkCommand)
import Client.State (changeSubfocus)
import Client.State.Focus (Subfocus(FocusChanList, FocusWho))
import Client.State.Network (sendMsg, csChannelList, clsElist, csPingStatus, _PingConnecting, csWhoReply, csNetwork)
import Client.WhoReply (newWhoReply)
import Control.Applicative (liftA2)
import Control.Lens (has, set, view)
import Control.Monad (unless)
import Data.Maybe (fromMaybe, maybeToList)
import Data.Text qualified as Text
import Irc.Commands
queryCommands :: CommandSection
queryCommands :: CommandSection
queryCommands = Text -> [Command] -> CommandSection
CommandSection Text
"Queries"
[ NonEmpty Text
-> Args ArgsContext (Maybe (String, Maybe String))
-> Text
-> CommandImpl (Maybe (String, Maybe String))
-> 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
"who")
(Args ArgsContext (String, Maybe String)
-> Args ArgsContext (Maybe (String, Maybe String))
forall r a. Args r a -> Args r (Maybe a)
optionalArg ((String -> Maybe String -> (String, Maybe String))
-> Ap (Arg ArgsContext) String
-> Ap (Arg ArgsContext) (Maybe String)
-> Args ArgsContext (String, Maybe String)
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 (,) (String -> Ap (Arg ArgsContext) String
forall r. String -> Args r String
simpleToken String
"[channel|nick|mask]") (Ap (Arg ArgsContext) String -> Ap (Arg ArgsContext) (Maybe String)
forall r a. Args r a -> Args r (Maybe a)
optionalArg (String -> Ap (Arg ArgsContext) String
forall r. String -> Args r String
simpleToken String
"[options]"))))
$(queriesDocs `cmdDoc` "who")
(CommandImpl (Maybe (String, Maybe String)) -> Command)
-> CommandImpl (Maybe (String, Maybe String)) -> Command
forall a b. (a -> b) -> a -> b
$ NetworkCommand (Maybe (String, Maybe String))
-> (Bool -> NetworkCommand String)
-> CommandImpl (Maybe (String, Maybe String))
forall a.
NetworkCommand a
-> (Bool -> NetworkCommand String) -> CommandImpl a
NetworkCommand NetworkCommand (Maybe (String, Maybe String))
cmdWho Bool -> NetworkCommand String
simpleNetworkTab
, NonEmpty Text
-> Ap (Arg ArgsContext) String
-> Text
-> CommandImpl String
-> 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
"whois")
(String -> Ap (Arg ArgsContext) String
forall r. String -> Args r String
remainingArg String
"arguments")
$(queriesDocs `cmdDoc` "whois")
(CommandImpl String -> Command) -> CommandImpl String -> Command
forall a b. (a -> b) -> a -> b
$ NetworkCommand String
-> (Bool -> NetworkCommand String) -> CommandImpl String
forall a.
NetworkCommand a
-> (Bool -> NetworkCommand String) -> CommandImpl a
NetworkCommand NetworkCommand String
cmdWhois Bool -> NetworkCommand String
simpleNetworkTab
, NonEmpty Text
-> Ap (Arg ArgsContext) String
-> Text
-> CommandImpl String
-> 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
"whowas")
(String -> Ap (Arg ArgsContext) String
forall r. String -> Args r String
remainingArg String
"arguments")
$(queriesDocs `cmdDoc` "whowas")
(CommandImpl String -> Command) -> CommandImpl String -> Command
forall a b. (a -> b) -> a -> b
$ NetworkCommand String
-> (Bool -> NetworkCommand String) -> CommandImpl String
forall a.
NetworkCommand a
-> (Bool -> NetworkCommand String) -> CommandImpl a
NetworkCommand NetworkCommand String
cmdWhowas Bool -> NetworkCommand String
simpleNetworkTab
, NonEmpty Text
-> Ap (Arg ArgsContext) String
-> Text
-> CommandImpl String
-> 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
"ison")
(String -> Ap (Arg ArgsContext) String
forall r. String -> Args r String
remainingArg String
"arguments")
$(queriesDocs `cmdDoc` "ison")
(CommandImpl String -> Command) -> CommandImpl String -> Command
forall a b. (a -> b) -> a -> b
$ NetworkCommand String
-> (Bool -> NetworkCommand String) -> CommandImpl String
forall a.
NetworkCommand a
-> (Bool -> NetworkCommand String) -> CommandImpl a
NetworkCommand NetworkCommand String
cmdIson Bool -> NetworkCommand String
simpleNetworkTab
, NonEmpty Text
-> Ap (Arg ArgsContext) String
-> Text
-> CommandImpl String
-> 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
"userhost")
(String -> Ap (Arg ArgsContext) String
forall r. String -> Args r String
remainingArg String
"arguments")
$(queriesDocs `cmdDoc` "userhost")
(CommandImpl String -> Command) -> CommandImpl String -> Command
forall a b. (a -> b) -> a -> b
$ NetworkCommand String
-> (Bool -> NetworkCommand String) -> CommandImpl String
forall a.
NetworkCommand a
-> (Bool -> NetworkCommand String) -> CommandImpl a
NetworkCommand NetworkCommand String
cmdUserhost Bool -> NetworkCommand String
simpleNetworkTab
, NonEmpty Text
-> Ap (Arg ArgsContext) (Maybe String)
-> Text
-> CommandImpl (Maybe String)
-> 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
"time")
(Ap (Arg ArgsContext) String -> Ap (Arg ArgsContext) (Maybe String)
forall r a. Args r a -> Args r (Maybe a)
optionalArg (String -> Ap (Arg ArgsContext) String
forall r. String -> Args r String
simpleToken String
"[servername]"))
$(queriesDocs `cmdDoc` "time")
(CommandImpl (Maybe String) -> Command)
-> CommandImpl (Maybe String) -> Command
forall a b. (a -> b) -> a -> b
$ NetworkCommand (Maybe String)
-> (Bool -> NetworkCommand String) -> CommandImpl (Maybe String)
forall a.
NetworkCommand a
-> (Bool -> NetworkCommand String) -> CommandImpl a
NetworkCommand NetworkCommand (Maybe String)
cmdTime Bool -> NetworkCommand String
simpleNetworkTab
, NonEmpty Text
-> Ap (Arg ArgsContext) String
-> Text
-> CommandImpl String
-> 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
"stats")
(String -> Ap (Arg ArgsContext) String
forall r. String -> Args r String
remainingArg String
"arguments")
$(queriesDocs `cmdDoc` "stats")
(CommandImpl String -> Command) -> CommandImpl String -> Command
forall a b. (a -> b) -> a -> b
$ NetworkCommand String
-> (Bool -> NetworkCommand String) -> CommandImpl String
forall a.
NetworkCommand a
-> (Bool -> NetworkCommand String) -> CommandImpl a
NetworkCommand NetworkCommand String
cmdStats Bool -> NetworkCommand String
simpleNetworkTab
, NonEmpty Text
-> Ap (Arg ArgsContext) (Maybe String)
-> Text
-> CommandImpl (Maybe String)
-> 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
"lusers")
(Ap (Arg ArgsContext) String -> Ap (Arg ArgsContext) (Maybe String)
forall r a. Args r a -> Args r (Maybe a)
optionalArg (String -> Ap (Arg ArgsContext) String
forall r. String -> Args r String
simpleToken String
"[servername]"))
$(queriesDocs `cmdDoc` "lusers")
(CommandImpl (Maybe String) -> Command)
-> CommandImpl (Maybe String) -> Command
forall a b. (a -> b) -> a -> b
$ NetworkCommand (Maybe String)
-> (Bool -> NetworkCommand String) -> CommandImpl (Maybe String)
forall a.
NetworkCommand a
-> (Bool -> NetworkCommand String) -> CommandImpl a
NetworkCommand NetworkCommand (Maybe String)
cmdLusers Bool -> NetworkCommand String
simpleNetworkTab
, NonEmpty Text
-> Ap (Arg ArgsContext) (Maybe String)
-> Text
-> CommandImpl (Maybe String)
-> 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
"users")
(Ap (Arg ArgsContext) String -> Ap (Arg ArgsContext) (Maybe String)
forall r a. Args r a -> Args r (Maybe a)
optionalArg (String -> Ap (Arg ArgsContext) String
forall r. String -> Args r String
simpleToken String
"[servername]"))
$(queriesDocs `cmdDoc` "users")
(CommandImpl (Maybe String) -> Command)
-> CommandImpl (Maybe String) -> Command
forall a b. (a -> b) -> a -> b
$ NetworkCommand (Maybe String)
-> (Bool -> NetworkCommand String) -> CommandImpl (Maybe String)
forall a.
NetworkCommand a
-> (Bool -> NetworkCommand String) -> CommandImpl a
NetworkCommand NetworkCommand (Maybe String)
cmdUsers Bool -> NetworkCommand String
simpleNetworkTab
, NonEmpty Text
-> Ap (Arg ArgsContext) (Maybe String)
-> Text
-> CommandImpl (Maybe String)
-> 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
"motd")
(Ap (Arg ArgsContext) String -> Ap (Arg ArgsContext) (Maybe String)
forall r a. Args r a -> Args r (Maybe a)
optionalArg (String -> Ap (Arg ArgsContext) String
forall r. String -> Args r String
simpleToken String
"[servername]"))
$(queriesDocs `cmdDoc` "motd")
(CommandImpl (Maybe String) -> Command)
-> CommandImpl (Maybe String) -> Command
forall a b. (a -> b) -> a -> b
$ NetworkCommand (Maybe String)
-> (Bool -> NetworkCommand String) -> CommandImpl (Maybe String)
forall a.
NetworkCommand a
-> (Bool -> NetworkCommand String) -> CommandImpl a
NetworkCommand NetworkCommand (Maybe String)
cmdMotd Bool -> NetworkCommand String
simpleNetworkTab
, NonEmpty Text
-> Ap (Arg ArgsContext) (Maybe String)
-> Text
-> CommandImpl (Maybe String)
-> 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
"admin")
(Ap (Arg ArgsContext) String -> Ap (Arg ArgsContext) (Maybe String)
forall r a. Args r a -> Args r (Maybe a)
optionalArg (String -> Ap (Arg ArgsContext) String
forall r. String -> Args r String
simpleToken String
"[servername]"))
$(queriesDocs `cmdDoc` "admin")
(CommandImpl (Maybe String) -> Command)
-> CommandImpl (Maybe String) -> Command
forall a b. (a -> b) -> a -> b
$ NetworkCommand (Maybe String)
-> (Bool -> NetworkCommand String) -> CommandImpl (Maybe String)
forall a.
NetworkCommand a
-> (Bool -> NetworkCommand String) -> CommandImpl a
NetworkCommand NetworkCommand (Maybe String)
cmdAdmin Bool -> NetworkCommand String
simpleNetworkTab
, NonEmpty Text
-> Ap (Arg ArgsContext) (Maybe String)
-> Text
-> CommandImpl (Maybe String)
-> 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
"rules")
(Ap (Arg ArgsContext) String -> Ap (Arg ArgsContext) (Maybe String)
forall r a. Args r a -> Args r (Maybe a)
optionalArg (String -> Ap (Arg ArgsContext) String
forall r. String -> Args r String
simpleToken String
"[servername]"))
$(queriesDocs `cmdDoc` "rules")
(CommandImpl (Maybe String) -> Command)
-> CommandImpl (Maybe String) -> Command
forall a b. (a -> b) -> a -> b
$ NetworkCommand (Maybe String)
-> (Bool -> NetworkCommand String) -> CommandImpl (Maybe String)
forall a.
NetworkCommand a
-> (Bool -> NetworkCommand String) -> CommandImpl a
NetworkCommand NetworkCommand (Maybe String)
cmdRules Bool -> NetworkCommand String
simpleNetworkTab
, NonEmpty Text
-> Args ArgsContext () -> Text -> CommandImpl () -> 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
"info")
(() -> Args ArgsContext ()
forall a. a -> Ap (Arg ArgsContext) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
$(queriesDocs `cmdDoc` "info")
(CommandImpl () -> Command) -> CommandImpl () -> Command
forall a b. (a -> b) -> a -> b
$ NetworkCommand ()
-> (Bool -> NetworkCommand String) -> CommandImpl ()
forall a.
NetworkCommand a
-> (Bool -> NetworkCommand String) -> CommandImpl a
NetworkCommand NetworkCommand ()
cmdInfo Bool -> NetworkCommand String
noNetworkTab
, NonEmpty Text
-> Args ArgsContext (Maybe (ListArgs, Maybe String))
-> Text
-> CommandImpl (Maybe (ListArgs, Maybe String))
-> 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
"list")
(Args ArgsContext (ListArgs, Maybe String)
-> Args ArgsContext (Maybe (ListArgs, Maybe String))
forall r a. Args r a -> Args r (Maybe a)
optionalArg ((ListArgs -> Maybe String -> (ListArgs, Maybe String))
-> Ap (Arg ArgsContext) ListArgs
-> Ap (Arg ArgsContext) (Maybe String)
-> Args ArgsContext (ListArgs, Maybe String)
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 (,) (String
-> (ArgsContext -> String -> Maybe ListArgs)
-> Ap (Arg ArgsContext) ListArgs
forall r a. String -> (r -> String -> Maybe a) -> Args r a
tokenArg String
"[clientopts]" ((String -> Maybe ListArgs)
-> ArgsContext -> String -> Maybe ListArgs
forall a b. a -> b -> a
const String -> Maybe ListArgs
lsaParse)) (Ap (Arg ArgsContext) String -> Ap (Arg ArgsContext) (Maybe String)
forall r a. Args r a -> Args r (Maybe a)
optionalArg (String -> Ap (Arg ArgsContext) String
forall r. String -> Args r String
simpleToken String
"[elist]"))))
$(queriesDocs `cmdDoc` "list")
(CommandImpl (Maybe (ListArgs, Maybe String)) -> Command)
-> CommandImpl (Maybe (ListArgs, Maybe String)) -> Command
forall a b. (a -> b) -> a -> b
$ NetworkCommand (Maybe (ListArgs, Maybe String))
-> (Bool -> NetworkCommand String)
-> CommandImpl (Maybe (ListArgs, Maybe String))
forall a.
NetworkCommand a
-> (Bool -> NetworkCommand String) -> CommandImpl a
NetworkCommand NetworkCommand (Maybe (ListArgs, Maybe String))
cmdList Bool -> NetworkCommand String
simpleNetworkTab
, NonEmpty Text
-> Ap (Arg ArgsContext) String
-> Text
-> CommandImpl String
-> 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
"links")
(String -> Ap (Arg ArgsContext) String
forall r. String -> Args r String
remainingArg String
"arguments")
$(queriesDocs `cmdDoc` "links")
(CommandImpl String -> Command) -> CommandImpl String -> Command
forall a b. (a -> b) -> a -> b
$ NetworkCommand String
-> (Bool -> NetworkCommand String) -> CommandImpl String
forall a.
NetworkCommand a
-> (Bool -> NetworkCommand String) -> CommandImpl a
NetworkCommand NetworkCommand String
cmdLinks Bool -> NetworkCommand String
simpleNetworkTab
, NonEmpty Text
-> Ap (Arg ArgsContext) (Maybe String)
-> Text
-> CommandImpl (Maybe String)
-> 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
"version")
(Ap (Arg ArgsContext) String -> Ap (Arg ArgsContext) (Maybe String)
forall r a. Args r a -> Args r (Maybe a)
optionalArg (String -> Ap (Arg ArgsContext) String
forall r. String -> Args r String
simpleToken String
"[servername]"))
$(queriesDocs `cmdDoc` "version")
(CommandImpl (Maybe String) -> Command)
-> CommandImpl (Maybe String) -> Command
forall a b. (a -> b) -> a -> b
$ NetworkCommand (Maybe String)
-> (Bool -> NetworkCommand String) -> CommandImpl (Maybe String)
forall a.
NetworkCommand a
-> (Bool -> NetworkCommand String) -> CommandImpl a
NetworkCommand NetworkCommand (Maybe String)
cmdVersion Bool -> NetworkCommand String
simpleNetworkTab
]
cmdInfo :: NetworkCommand ()
cmdInfo :: NetworkCommand ()
cmdInfo NetworkState
cs ClientState
st ()
_ =
do NetworkState -> RawIrcMsg -> IO ()
sendMsg NetworkState
cs RawIrcMsg
ircInfo
ClientState -> IO CommandResult
forall (m :: * -> *). Monad m => ClientState -> m CommandResult
commandSuccess ClientState
st
cmdVersion :: NetworkCommand (Maybe String)
cmdVersion :: NetworkCommand (Maybe String)
cmdVersion NetworkState
cs ClientState
st Maybe String
mbservername =
do NetworkState -> RawIrcMsg -> IO ()
sendMsg NetworkState
cs (RawIrcMsg -> IO ()) -> RawIrcMsg -> IO ()
forall a b. (a -> b) -> a -> b
$ Text -> RawIrcMsg
ircVersion (Text -> RawIrcMsg) -> Text -> RawIrcMsg
forall a b. (a -> b) -> a -> b
$ case Maybe String
mbservername of
Just String
s -> String -> Text
Text.pack String
s
Maybe String
Nothing -> Text
""
ClientState -> IO CommandResult
forall (m :: * -> *). Monad m => ClientState -> m CommandResult
commandSuccess ClientState
st
cmdList :: NetworkCommand (Maybe (ListArgs, Maybe String))
cmdList :: NetworkCommand (Maybe (ListArgs, Maybe String))
cmdList NetworkState
cs ClientState
st Maybe (ListArgs, Maybe String)
rest =
do
let (ListArgs
lsa, Maybe String
maybeElist) = (ListArgs, Maybe String)
-> Maybe (ListArgs, Maybe String) -> (ListArgs, Maybe String)
forall a. a -> Maybe a -> a
fromMaybe (ListArgs
lsaDefault, Maybe String
forall a. Maybe a
Nothing) Maybe (ListArgs, Maybe String)
rest
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
let elist :: Maybe Text
elist = Text -> Maybe Text
forall a. a -> Maybe a
Just (String -> Text
Text.pack (String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe String
"" Maybe String
maybeElist))
let cached :: Bool
cached = Maybe Text
elist Maybe Text -> Maybe Text -> Bool
forall a. Eq a => a -> a -> Bool
== Getting (Maybe Text) NetworkState (Maybe Text)
-> NetworkState -> Maybe Text
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view ((ChannelList -> Const (Maybe Text) ChannelList)
-> NetworkState -> Const (Maybe Text) NetworkState
Lens' NetworkState ChannelList
csChannelList ((ChannelList -> Const (Maybe Text) ChannelList)
-> NetworkState -> Const (Maybe Text) NetworkState)
-> ((Maybe Text -> Const (Maybe Text) (Maybe Text))
-> ChannelList -> Const (Maybe Text) ChannelList)
-> Getting (Maybe Text) NetworkState (Maybe Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe Text -> Const (Maybe Text) (Maybe Text))
-> ChannelList -> Const (Maybe Text) ChannelList
Lens' ChannelList (Maybe Text)
clsElist) NetworkState
cs
let sendM :: IO ()
sendM = NetworkState -> RawIrcMsg -> IO ()
sendMsg NetworkState
cs ([Text] -> RawIrcMsg
ircList (String -> Text
Text.pack (String -> Text) -> [String] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe String -> [String]
forall a. Maybe a -> [a]
maybeToList Maybe String
maybeElist))
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Bool
connecting Bool -> Bool -> Bool
|| (Bool
cached Bool -> Bool -> Bool
&& Bool -> Bool
not (ListArgs -> Bool
_lsaRefresh ListArgs
lsa))) IO ()
sendM
let cs' :: NetworkState
cs' = ASetter NetworkState NetworkState (Maybe Text) (Maybe Text)
-> Maybe Text -> NetworkState -> NetworkState
forall s t a b. ASetter s t a b -> b -> s -> t
set ((ChannelList -> Identity ChannelList)
-> NetworkState -> Identity NetworkState
Lens' NetworkState ChannelList
csChannelList ((ChannelList -> Identity ChannelList)
-> NetworkState -> Identity NetworkState)
-> ((Maybe Text -> Identity (Maybe Text))
-> ChannelList -> Identity ChannelList)
-> ASetter NetworkState NetworkState (Maybe Text) (Maybe Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe Text -> Identity (Maybe Text))
-> ChannelList -> Identity ChannelList
Lens' ChannelList (Maybe Text)
clsElist) Maybe Text
elist NetworkState
cs
let subfocus :: Subfocus
subfocus = Text -> Maybe Int -> Maybe Int -> Subfocus
FocusChanList (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) (ListArgs -> Maybe Int
_lsaMin ListArgs
lsa) (ListArgs -> Maybe Int
_lsaMax ListArgs
lsa)
NetworkState -> ClientState -> IO CommandResult
commandSuccessUpdateCS NetworkState
cs' (Subfocus -> ClientState -> ClientState
changeSubfocus Subfocus
subfocus ClientState
st)
data ListArgs = ListArgs
{ ListArgs -> Bool
_lsaRefresh :: Bool
, ListArgs -> Maybe Int
_lsaMin :: Maybe Int
, ListArgs -> Maybe Int
_lsaMax :: Maybe Int
}
lsaDefault :: ListArgs
lsaDefault :: ListArgs
lsaDefault = ListArgs
{ _lsaRefresh :: Bool
_lsaRefresh = Bool
False
, _lsaMin :: Maybe Int
_lsaMin = Maybe Int
forall a. Maybe a
Nothing
, _lsaMax :: Maybe Int
_lsaMax = Maybe Int
forall a. Maybe a
Nothing
}
lsaParse :: String -> Maybe ListArgs
lsaParse :: String -> Maybe ListArgs
lsaParse = ListArgs -> String -> Maybe ListArgs
lsaParse' ListArgs
lsaDefault
where
lsaParse' :: ListArgs -> String -> Maybe ListArgs
lsaParse' ListArgs
lsa String
str = case String
str of
Char
'~':String
rest -> ListArgs -> String -> Maybe ListArgs
lsaParse' ListArgs
lsa{ _lsaRefresh = True } String
rest
Char
',':String
rest -> ListArgs -> String -> Maybe ListArgs
lsaParse' ListArgs
lsa String
rest
Char
'>':(ReadS Int
forall a. Read a => ReadS a
reads -> [(Int
min', String
rest)]) | Int
min' Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0 ->
ListArgs -> String -> Maybe ListArgs
lsaParse' ListArgs
lsa{ _lsaMin = Just min'} String
rest
Char
'<':(ReadS Int
forall a. Read a => ReadS a
reads -> [(Int
max', String
rest)]) | Int
max' Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0 ->
ListArgs -> String -> Maybe ListArgs
lsaParse' ListArgs
lsa{ _lsaMax = Just max'} String
rest
String
"" -> ListArgs -> Maybe ListArgs
forall a. a -> Maybe a
Just ListArgs
lsa
String
_ -> Maybe ListArgs
forall a. Maybe a
Nothing
cmdLusers :: NetworkCommand (Maybe String)
cmdLusers :: NetworkCommand (Maybe String)
cmdLusers NetworkState
cs ClientState
st Maybe String
arg =
do NetworkState -> RawIrcMsg -> IO ()
sendMsg NetworkState
cs (RawIrcMsg -> IO ()) -> RawIrcMsg -> IO ()
forall a b. (a -> b) -> a -> b
$ [Text] -> RawIrcMsg
ircLusers ([Text] -> RawIrcMsg) -> [Text] -> RawIrcMsg
forall a b. (a -> b) -> a -> b
$ (String -> Text) -> [String] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Text
Text.pack ([String] -> [Text]) -> [String] -> [Text]
forall a b. (a -> b) -> a -> b
$
case Maybe String
arg of
Maybe String
Nothing -> []
Just String
x -> [String
"*", String
x]
ClientState -> IO CommandResult
forall (m :: * -> *). Monad m => ClientState -> m CommandResult
commandSuccess ClientState
st
cmdUsers :: NetworkCommand (Maybe String)
cmdUsers :: NetworkCommand (Maybe String)
cmdUsers NetworkState
cs ClientState
st Maybe String
arg =
do NetworkState -> RawIrcMsg -> IO ()
sendMsg NetworkState
cs (RawIrcMsg -> IO ()) -> RawIrcMsg -> IO ()
forall a b. (a -> b) -> a -> b
$ Text -> RawIrcMsg
ircUsers (Text -> RawIrcMsg) -> Text -> RawIrcMsg
forall a b. (a -> b) -> a -> b
$ Text -> (String -> Text) -> Maybe String -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
"" String -> Text
Text.pack Maybe String
arg
ClientState -> IO CommandResult
forall (m :: * -> *). Monad m => ClientState -> m CommandResult
commandSuccess ClientState
st
cmdMotd :: NetworkCommand (Maybe String)
cmdMotd :: NetworkCommand (Maybe String)
cmdMotd NetworkState
cs ClientState
st Maybe String
mbservername =
do NetworkState -> RawIrcMsg -> IO ()
sendMsg NetworkState
cs (RawIrcMsg -> IO ()) -> RawIrcMsg -> IO ()
forall a b. (a -> b) -> a -> b
$ Text -> RawIrcMsg
ircMotd (Text -> RawIrcMsg) -> Text -> RawIrcMsg
forall a b. (a -> b) -> a -> b
$ case Maybe String
mbservername of
Just String
s -> String -> Text
Text.pack String
s
Maybe String
Nothing -> Text
""
ClientState -> IO CommandResult
forall (m :: * -> *). Monad m => ClientState -> m CommandResult
commandSuccess ClientState
st
cmdAdmin :: NetworkCommand (Maybe String)
cmdAdmin :: NetworkCommand (Maybe String)
cmdAdmin NetworkState
cs ClientState
st Maybe String
mbservername =
do NetworkState -> RawIrcMsg -> IO ()
sendMsg NetworkState
cs (RawIrcMsg -> IO ()) -> RawIrcMsg -> IO ()
forall a b. (a -> b) -> a -> b
$ Text -> RawIrcMsg
ircAdmin (Text -> RawIrcMsg) -> Text -> RawIrcMsg
forall a b. (a -> b) -> a -> b
$ case Maybe String
mbservername of
Just String
s -> String -> Text
Text.pack String
s
Maybe String
Nothing -> Text
""
ClientState -> IO CommandResult
forall (m :: * -> *). Monad m => ClientState -> m CommandResult
commandSuccess ClientState
st
cmdRules :: NetworkCommand (Maybe String)
cmdRules :: NetworkCommand (Maybe String)
cmdRules NetworkState
cs ClientState
st Maybe String
mbservername =
do NetworkState -> RawIrcMsg -> IO ()
sendMsg NetworkState
cs (RawIrcMsg -> IO ()) -> RawIrcMsg -> IO ()
forall a b. (a -> b) -> a -> b
$ Text -> RawIrcMsg
ircRules (Text -> RawIrcMsg) -> Text -> RawIrcMsg
forall a b. (a -> b) -> a -> b
$
case Maybe String
mbservername of
Just String
s -> String -> Text
Text.pack String
s
Maybe String
Nothing -> Text
""
ClientState -> IO CommandResult
forall (m :: * -> *). Monad m => ClientState -> m CommandResult
commandSuccess ClientState
st
cmdStats :: NetworkCommand String
cmdStats :: NetworkCommand String
cmdStats NetworkState
cs ClientState
st String
rest =
do NetworkState -> RawIrcMsg -> IO ()
sendMsg NetworkState
cs ([Text] -> RawIrcMsg
ircStats (String -> Text
Text.pack (String -> Text) -> [String] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> [String]
words String
rest))
ClientState -> IO CommandResult
forall (m :: * -> *). Monad m => ClientState -> m CommandResult
commandSuccess ClientState
st
cmdLinks :: NetworkCommand String
cmdLinks :: NetworkCommand String
cmdLinks NetworkState
cs ClientState
st String
rest =
do NetworkState -> RawIrcMsg -> IO ()
sendMsg NetworkState
cs ([Text] -> RawIrcMsg
ircLinks (String -> Text
Text.pack (String -> Text) -> [String] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> [String]
words String
rest))
ClientState -> IO CommandResult
forall (m :: * -> *). Monad m => ClientState -> m CommandResult
commandSuccess ClientState
st
cmdTime :: NetworkCommand (Maybe String)
cmdTime :: NetworkCommand (Maybe String)
cmdTime NetworkState
cs ClientState
st Maybe String
arg =
do NetworkState -> RawIrcMsg -> IO ()
sendMsg NetworkState
cs (Text -> RawIrcMsg
ircTime (Text -> (String -> Text) -> Maybe String -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
"" String -> Text
Text.pack Maybe String
arg))
ClientState -> IO CommandResult
forall (m :: * -> *). Monad m => ClientState -> m CommandResult
commandSuccess ClientState
st
cmdWhois :: NetworkCommand String
cmdWhois :: NetworkCommand String
cmdWhois NetworkState
cs ClientState
st String
rest =
do NetworkState -> RawIrcMsg -> IO ()
sendMsg NetworkState
cs ([Text] -> RawIrcMsg
ircWhois (String -> Text
Text.pack (String -> Text) -> [String] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> [String]
words String
rest))
ClientState -> IO CommandResult
forall (m :: * -> *). Monad m => ClientState -> m CommandResult
commandSuccess ClientState
st
cmdWho :: NetworkCommand (Maybe (String, Maybe String))
cmdWho :: NetworkCommand (Maybe (String, Maybe String))
cmdWho NetworkState
cs ClientState
st Maybe (String, Maybe String)
Nothing = ClientState -> IO CommandResult
forall (m :: * -> *). Monad m => ClientState -> m CommandResult
commandSuccess (ClientState -> IO CommandResult)
-> ClientState -> IO CommandResult
forall a b. (a -> b) -> a -> b
$ Subfocus -> ClientState -> ClientState
changeSubfocus (Text -> Subfocus
FocusWho (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)) ClientState
st
cmdWho NetworkState
cs ClientState
st (Just (String
query, Maybe String
arg)) =
do
let query' :: Text
query' = String -> Text
Text.pack String
query
let arg' :: String
arg' = String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe String
"" Maybe String
arg
let cs' :: NetworkState
cs' = ASetter NetworkState NetworkState WhoReply WhoReply
-> WhoReply -> NetworkState -> NetworkState
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter NetworkState NetworkState WhoReply WhoReply
Lens' NetworkState WhoReply
csWhoReply (Text -> String -> WhoReply
newWhoReply Text
query' String
arg') NetworkState
cs
NetworkState -> RawIrcMsg -> IO ()
sendMsg NetworkState
cs ([Text] -> RawIrcMsg
ircWho (Text
query' Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: Maybe Text -> [Text]
forall a. Maybe a -> [a]
maybeToList (String -> Text
Text.pack (String -> Text) -> Maybe String -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe String
arg)))
NetworkState -> ClientState -> IO CommandResult
commandSuccessUpdateCS NetworkState
cs' (ClientState -> IO CommandResult)
-> ClientState -> IO CommandResult
forall a b. (a -> b) -> a -> b
$ Subfocus -> ClientState -> ClientState
changeSubfocus (Text -> Subfocus
FocusWho (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)) ClientState
st
cmdWhowas :: NetworkCommand String
cmdWhowas :: NetworkCommand String
cmdWhowas NetworkState
cs ClientState
st String
rest =
do NetworkState -> RawIrcMsg -> IO ()
sendMsg NetworkState
cs ([Text] -> RawIrcMsg
ircWhowas (String -> Text
Text.pack (String -> Text) -> [String] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> [String]
words String
rest))
ClientState -> IO CommandResult
forall (m :: * -> *). Monad m => ClientState -> m CommandResult
commandSuccess ClientState
st
cmdIson :: NetworkCommand String
cmdIson :: NetworkCommand String
cmdIson NetworkState
cs ClientState
st String
rest =
do NetworkState -> RawIrcMsg -> IO ()
sendMsg NetworkState
cs ([Text] -> RawIrcMsg
ircIson (String -> Text
Text.pack (String -> Text) -> [String] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> [String]
words String
rest))
ClientState -> IO CommandResult
forall (m :: * -> *). Monad m => ClientState -> m CommandResult
commandSuccess ClientState
st
cmdUserhost :: NetworkCommand String
cmdUserhost :: NetworkCommand String
cmdUserhost NetworkState
cs ClientState
st String
rest =
do NetworkState -> RawIrcMsg -> IO ()
sendMsg NetworkState
cs ([Text] -> RawIrcMsg
ircUserhost (String -> Text
Text.pack (String -> Text) -> [String] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> [String]
words String
rest))
ClientState -> IO CommandResult
forall (m :: * -> *). Monad m => ClientState -> m CommandResult
commandSuccess ClientState
st