{-# Language OverloadedStrings, TemplateHaskell #-}
module Client.Commands.Toggles (togglesCommands) where
import Client.Commands.Docs (togglesDocs, cmdDoc)
import Client.Commands.TabCompletion (noClientTab)
import Client.Commands.Types
import Client.Configuration (EditMode(SingleLineEditor, MultiLineEditor), LayoutMode(OneColumn, TwoColumn))
import Client.State
import Control.Lens (over, set)
togglesCommands :: CommandSection
togglesCommands :: CommandSection
togglesCommands = Text -> [Command] -> CommandSection
CommandSection Text
"View toggles"
[ 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
"toggle-detail")
(() -> Args ArgsContext ()
forall a. a -> Ap (Arg ArgsContext) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
$(togglesDocs `cmdDoc` "toggle-detail")
(CommandImpl () -> Command) -> CommandImpl () -> Command
forall a b. (a -> b) -> a -> b
$ ClientCommand ()
-> (Bool -> ClientCommand String) -> CommandImpl ()
forall a.
ClientCommand a -> (Bool -> ClientCommand String) -> CommandImpl a
ClientCommand ClientCommand ()
cmdToggleDetail Bool -> ClientCommand String
noClientTab
, 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
"toggle-activity-bar")
(() -> Args ArgsContext ()
forall a. a -> Ap (Arg ArgsContext) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
$(togglesDocs `cmdDoc` "toggle-activity-bar")
(CommandImpl () -> Command) -> CommandImpl () -> Command
forall a b. (a -> b) -> a -> b
$ ClientCommand ()
-> (Bool -> ClientCommand String) -> CommandImpl ()
forall a.
ClientCommand a -> (Bool -> ClientCommand String) -> CommandImpl a
ClientCommand ClientCommand ()
cmdToggleActivityBar Bool -> ClientCommand String
noClientTab
, 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
"toggle-show-ping")
(() -> Args ArgsContext ()
forall a. a -> Ap (Arg ArgsContext) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
$(togglesDocs `cmdDoc` "toggle-show-ping")
(CommandImpl () -> Command) -> CommandImpl () -> Command
forall a b. (a -> b) -> a -> b
$ ClientCommand ()
-> (Bool -> ClientCommand String) -> CommandImpl ()
forall a.
ClientCommand a -> (Bool -> ClientCommand String) -> CommandImpl a
ClientCommand ClientCommand ()
cmdToggleShowPing Bool -> ClientCommand String
noClientTab
, 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
"toggle-metadata")
(() -> Args ArgsContext ()
forall a. a -> Ap (Arg ArgsContext) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
$(togglesDocs `cmdDoc` "toggle-metadata")
(CommandImpl () -> Command) -> CommandImpl () -> Command
forall a b. (a -> b) -> a -> b
$ ClientCommand ()
-> (Bool -> ClientCommand String) -> CommandImpl ()
forall a.
ClientCommand a -> (Bool -> ClientCommand String) -> CommandImpl a
ClientCommand ClientCommand ()
cmdToggleMetadata Bool -> ClientCommand String
noClientTab
, 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
"toggle-layout")
(() -> Args ArgsContext ()
forall a. a -> Ap (Arg ArgsContext) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
$(togglesDocs `cmdDoc` "toggle-layout")
(CommandImpl () -> Command) -> CommandImpl () -> Command
forall a b. (a -> b) -> a -> b
$ ClientCommand ()
-> (Bool -> ClientCommand String) -> CommandImpl ()
forall a.
ClientCommand a -> (Bool -> ClientCommand String) -> CommandImpl a
ClientCommand ClientCommand ()
cmdToggleLayout Bool -> ClientCommand String
noClientTab
, 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
"toggle-editor")
(() -> Args ArgsContext ()
forall a. a -> Ap (Arg ArgsContext) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
$(togglesDocs `cmdDoc` "toggle-editor")
(CommandImpl () -> Command) -> CommandImpl () -> Command
forall a b. (a -> b) -> a -> b
$ ClientCommand ()
-> (Bool -> ClientCommand String) -> CommandImpl ()
forall a.
ClientCommand a -> (Bool -> ClientCommand String) -> CommandImpl a
ClientCommand ClientCommand ()
cmdToggleEditor Bool -> ClientCommand String
noClientTab
, 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
"toggle-edit-lock")
(() -> Args ArgsContext ()
forall a. a -> Ap (Arg ArgsContext) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
$(togglesDocs `cmdDoc` "toggle-edit-lock")
(CommandImpl () -> Command) -> CommandImpl () -> Command
forall a b. (a -> b) -> a -> b
$ ClientCommand ()
-> (Bool -> ClientCommand String) -> CommandImpl ()
forall a.
ClientCommand a -> (Bool -> ClientCommand String) -> CommandImpl a
ClientCommand ClientCommand ()
cmdToggleEditLock Bool -> ClientCommand String
noClientTab
]
cmdToggleDetail :: ClientCommand ()
cmdToggleDetail :: ClientCommand ()
cmdToggleDetail ClientState
st ()
_ = ClientState -> IO CommandResult
forall (m :: * -> *). Monad m => ClientState -> m CommandResult
commandSuccess (ASetter ClientState ClientState Bool Bool
-> (Bool -> Bool) -> ClientState -> ClientState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter ClientState ClientState Bool Bool
Lens' ClientState Bool
clientDetailView Bool -> Bool
not ClientState
st)
cmdToggleActivityBar :: ClientCommand ()
cmdToggleActivityBar :: ClientCommand ()
cmdToggleActivityBar ClientState
st ()
_ = ClientState -> IO CommandResult
forall (m :: * -> *). Monad m => ClientState -> m CommandResult
commandSuccess (ASetter ClientState ClientState Bool Bool
-> (Bool -> Bool) -> ClientState -> ClientState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter ClientState ClientState Bool Bool
Lens' ClientState Bool
clientActivityBar Bool -> Bool
not ClientState
st)
cmdToggleShowPing :: ClientCommand ()
cmdToggleShowPing :: ClientCommand ()
cmdToggleShowPing ClientState
st ()
_ = ClientState -> IO CommandResult
forall (m :: * -> *). Monad m => ClientState -> m CommandResult
commandSuccess (ASetter ClientState ClientState Bool Bool
-> (Bool -> Bool) -> ClientState -> ClientState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter ClientState ClientState Bool Bool
Lens' ClientState Bool
clientShowPing Bool -> Bool
not ClientState
st)
cmdToggleMetadata :: ClientCommand ()
cmdToggleMetadata :: ClientCommand ()
cmdToggleMetadata ClientState
st ()
_ = ClientState -> IO CommandResult
forall (m :: * -> *). Monad m => ClientState -> m CommandResult
commandSuccess (ClientState -> ClientState
clientToggleHideMeta ClientState
st)
cmdToggleLayout :: ClientCommand ()
cmdToggleLayout :: ClientCommand ()
cmdToggleLayout ClientState
st ()
_ = ClientState -> IO CommandResult
forall (m :: * -> *). Monad m => ClientState -> m CommandResult
commandSuccess (ASetter ClientState ClientState Int Int
-> Int -> ClientState -> ClientState
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter ClientState ClientState Int Int
Lens' ClientState Int
clientScroll Int
0 (ASetter ClientState ClientState LayoutMode LayoutMode
-> (LayoutMode -> LayoutMode) -> ClientState -> ClientState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter ClientState ClientState LayoutMode LayoutMode
Lens' ClientState LayoutMode
clientLayout LayoutMode -> LayoutMode
aux ClientState
st))
where
aux :: LayoutMode -> LayoutMode
aux LayoutMode
OneColumn = LayoutMode
TwoColumn
aux LayoutMode
TwoColumn = LayoutMode
OneColumn
cmdToggleEditor :: ClientCommand ()
cmdToggleEditor :: ClientCommand ()
cmdToggleEditor ClientState
st ()
_ = ClientState -> IO CommandResult
forall (m :: * -> *). Monad m => ClientState -> m CommandResult
commandSuccess (ASetter ClientState ClientState EditMode EditMode
-> (EditMode -> EditMode) -> ClientState -> ClientState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter ClientState ClientState EditMode EditMode
Lens' ClientState EditMode
clientEditMode EditMode -> EditMode
aux ClientState
st)
where
aux :: EditMode -> EditMode
aux EditMode
SingleLineEditor = EditMode
MultiLineEditor
aux EditMode
MultiLineEditor = EditMode
SingleLineEditor
cmdToggleEditLock :: ClientCommand ()
cmdToggleEditLock :: ClientCommand ()
cmdToggleEditLock ClientState
st ()
_ = ClientState -> IO CommandResult
forall (m :: * -> *). Monad m => ClientState -> m CommandResult
commandSuccess (ASetter ClientState ClientState Bool Bool
-> (Bool -> Bool) -> ClientState -> ClientState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter ClientState ClientState Bool Bool
Lens' ClientState Bool
clientEditLock Bool -> Bool
not ClientState
st)