module Chiasma.Data.TmuxCommand where

import Data.List (dropWhileEnd)
import qualified Data.Text as Text
import Exon (exon)
import Text.Show (shows)

import Chiasma.Class.CmdArgs (cmdArgs)
import qualified Chiasma.Codec as Codec
import Chiasma.Codec (multi, single)
import Chiasma.Codec.Data.Client (Client)
import Chiasma.Codec.Data.Pane (Pane)
import Chiasma.Codec.Data.Session (Session)
import Chiasma.Codec.Data.Window (Window)
import Chiasma.Data.CapturePaneParams (CapturePaneParams (CapturePaneParams), stripBlank, stripTrailingWs)
import Chiasma.Data.CopyModeParams (CopyModeParams)
import Chiasma.Data.DecodeError (DecodeError)
import Chiasma.Data.KillPaneParams (KillPaneParams)
import Chiasma.Data.PaneSelection (PaneSelection)
import Chiasma.Data.PipePaneParams (PipePaneParams)
import Chiasma.Data.ResizePaneParams (ResizePaneParams)
import Chiasma.Data.SelectParams (SelectParams)
import Chiasma.Data.SelectWindowParams (SelectWindowParams)
import Chiasma.Data.SendKeysParams (SendKeysParams)
import Chiasma.Data.SessionParams (SessionParams)
import Chiasma.Data.SplitParams (JoinPaneParams, SplitWindowParams)
import Chiasma.Data.Target (Target)
import Chiasma.Data.TmuxId (ClientId (ClientId))
import Chiasma.Data.TmuxQuery (TmuxQuery)
import Chiasma.Data.TmuxRequest (TmuxRequest (TmuxRequest))
import Chiasma.Data.TmuxResponse (TmuxResponse (TmuxResponse))
import Chiasma.Data.WindowParams (WindowParams)
import Chiasma.Data.WindowSelection (WindowSelection)
import Chiasma.Function (applyWhen)

data TmuxCommand :: Type -> Type where
  Fmap :: (a -> b) -> TmuxCommand a -> TmuxCommand b
  ListPanes :: PaneSelection -> TmuxCommand [Pane]
  ListWindows :: WindowSelection -> TmuxCommand [Window]
  ListSessions :: TmuxCommand [Session]
  ListClients :: TmuxCommand [Client]
  SwitchClient :: ClientId -> Target -> TmuxCommand ()
  NewWindow :: WindowParams -> TmuxCommand Window
  SplitWindow :: WindowParams -> SplitWindowParams -> TmuxCommand Pane
  SelectWindow :: SelectWindowParams -> TmuxCommand ()
  NewSession :: SessionParams -> TmuxCommand Session
  CopyMode :: CopyModeParams -> TmuxCommand ()
  SendKeys :: SendKeysParams -> TmuxCommand ()
  SelectPane :: SelectParams -> TmuxCommand ()
  KillPane :: KillPaneParams -> TmuxCommand ()
  MovePane :: JoinPaneParams -> TmuxCommand ()
  ResizePane :: ResizePaneParams -> TmuxCommand ()
  PipePane :: PipePaneParams -> TmuxCommand ()
  CapturePane :: CapturePaneParams -> TmuxCommand [Text]
  KillServer :: TmuxCommand ()

instance Functor TmuxCommand where
  fmap :: forall a b. (a -> b) -> TmuxCommand a -> TmuxCommand b
fmap = (a -> b) -> TmuxCommand a -> TmuxCommand b
forall a b. (a -> b) -> TmuxCommand a -> TmuxCommand b
Fmap

instance Show (TmuxCommand a) where
  showsPrec :: Int -> TmuxCommand a -> ShowS
showsPrec Int
d = \case
    Fmap a -> a
_ TmuxCommand a
cmd ->
      Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) [exon|Fmap #{showsPrec 11 cmd}|]
    ListPanes PaneSelection
sel ->
      Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) [exon|ListPanes #{showsPrec 11 sel}|]
    ListWindows WindowSelection
sel ->
      Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) [exon|ListWindows #{showsPrec 11 sel}|]
    TmuxCommand a
ListClients ->
      String -> ShowS
showString String
"ListClients"
    TmuxCommand a
ListSessions ->
      String -> ShowS
showString String
"ListSessions"
    SwitchClient ClientId
c Target
t ->
      Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) [exon|SwitchClient #{showsPrec 11 c} #{showsPrec 11 t}|]
    NewWindow WindowParams
params ->
      Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) [exon|NewWindow #{showsPrec 11 params}|]
    SplitWindow WindowParams
wParams SplitWindowParams
sParams ->
      Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) [exon|SplitWindow #{showsPrec 11 wParams} #{showsPrec 11 sParams}|]
    SelectWindow SelectWindowParams
params ->
      Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) [exon|SelectWindow #{showsPrec 11 params}|]
    NewSession SessionParams
params ->
      Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) [exon|NewSession #{showsPrec 11 params}|]
    CopyMode CopyModeParams
params ->
      Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) [exon|SelectPane #{showsPrec 11 params}|]
    SendKeys SendKeysParams
params ->
      Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) [exon|SendKeys #{showsPrec 11 params}|]
    SelectPane SelectParams
paneId ->
      Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) [exon|SelectPane #{shows paneId}|]
    KillPane KillPaneParams
params ->
      Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) [exon|KillPane #{showsPrec 11 params}|]
    MovePane JoinPaneParams
params ->
      Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) [exon|MovePane #{showsPrec 11 params}|]
    ResizePane ResizePaneParams
params ->
      Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) [exon|ResizePane #{showsPrec 11 params}|]
    PipePane PipePaneParams
params ->
      Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) [exon|PipePane #{showsPrec 11 params}|]
    CapturePane CapturePaneParams
params ->
      Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) [exon|CapturePane #{showsPrec 11 params}|]
    TmuxCommand a
KillServer ->
      String -> ShowS
showString String
"KillServer"

query ::
   a .
  TmuxCommand a ->
  Maybe TmuxQuery
query :: forall a. TmuxCommand a -> Maybe TmuxQuery
query = \case
  Fmap a -> a
_ TmuxCommand a
cmd -> TmuxCommand a -> Maybe TmuxQuery
forall a. TmuxCommand a -> Maybe TmuxQuery
query TmuxCommand a
cmd
  ListPanes PaneSelection
_ -> TmuxQuery -> Maybe TmuxQuery
forall a. a -> Maybe a
Just (forall a. TmuxCodec a => TmuxQuery
Codec.query @Pane)
  ListWindows WindowSelection
_ -> TmuxQuery -> Maybe TmuxQuery
forall a. a -> Maybe a
Just (forall a. TmuxCodec a => TmuxQuery
Codec.query @Window)
  TmuxCommand a
ListSessions -> TmuxQuery -> Maybe TmuxQuery
forall a. a -> Maybe a
Just (forall a. TmuxCodec a => TmuxQuery
Codec.query @Session)
  TmuxCommand a
ListClients -> TmuxQuery -> Maybe TmuxQuery
forall a. a -> Maybe a
Just (forall a. TmuxCodec a => TmuxQuery
Codec.query @Client)
  SwitchClient ClientId
_ Target
_ -> Maybe TmuxQuery
forall a. Maybe a
Nothing
  NewWindow WindowParams
_ -> TmuxQuery -> Maybe TmuxQuery
forall a. a -> Maybe a
Just (forall a. TmuxCodec a => TmuxQuery
Codec.query @Window)
  SplitWindow WindowParams
_ SplitWindowParams
_ -> TmuxQuery -> Maybe TmuxQuery
forall a. a -> Maybe a
Just (forall a. TmuxCodec a => TmuxQuery
Codec.query @Pane)
  SelectWindow SelectWindowParams
_ -> Maybe TmuxQuery
forall a. Maybe a
Nothing
  NewSession SessionParams
_ -> TmuxQuery -> Maybe TmuxQuery
forall a. a -> Maybe a
Just (forall a. TmuxCodec a => TmuxQuery
Codec.query @Session)
  CopyMode CopyModeParams
_ -> Maybe TmuxQuery
forall a. Maybe a
Nothing
  SendKeys SendKeysParams
_ -> Maybe TmuxQuery
forall a. Maybe a
Nothing
  SelectPane SelectParams
_ -> Maybe TmuxQuery
forall a. Maybe a
Nothing
  KillPane KillPaneParams
_ -> Maybe TmuxQuery
forall a. Maybe a
Nothing
  MovePane JoinPaneParams
_ -> Maybe TmuxQuery
forall a. Maybe a
Nothing
  ResizePane ResizePaneParams
_ -> Maybe TmuxQuery
forall a. Maybe a
Nothing
  PipePane PipePaneParams
_ -> Maybe TmuxQuery
forall a. Maybe a
Nothing
  CapturePane CapturePaneParams
_ -> Maybe TmuxQuery
forall a. Maybe a
Nothing
  TmuxCommand a
KillServer -> Maybe TmuxQuery
forall a. Maybe a
Nothing

request :: TmuxCommand a -> Maybe TmuxQuery -> TmuxRequest
request :: forall a. TmuxCommand a -> Maybe TmuxQuery -> TmuxRequest
request = \case
  Fmap a -> a
_ TmuxCommand a
c ->
    TmuxCommand a -> Maybe TmuxQuery -> TmuxRequest
forall a. TmuxCommand a -> Maybe TmuxQuery -> TmuxRequest
request TmuxCommand a
c
  ListPanes PaneSelection
selection ->
    Text -> [Text] -> Maybe TmuxQuery -> TmuxRequest
TmuxRequest Text
"list-panes" (PaneSelection -> [Text]
forall a. CmdArgs a => a -> [Text]
cmdArgs PaneSelection
selection)
  ListWindows WindowSelection
selection ->
    Text -> [Text] -> Maybe TmuxQuery -> TmuxRequest
TmuxRequest Text
"list-windows" (WindowSelection -> [Text]
forall a. CmdArgs a => a -> [Text]
cmdArgs WindowSelection
selection)
  TmuxCommand a
ListSessions ->
    Text -> [Text] -> Maybe TmuxQuery -> TmuxRequest
TmuxRequest Text
"list-sessions" []
  TmuxCommand a
ListClients ->
    Text -> [Text] -> Maybe TmuxQuery -> TmuxRequest
TmuxRequest Text
"list-clients" []
  SwitchClient (ClientId Text
client) Target
target ->
    Text -> [Text] -> Maybe TmuxQuery -> TmuxRequest
TmuxRequest Text
"switch-client" ([Text
Item [Text]
"-c", Text
Item [Text]
client] [Text] -> [Text] -> [Text]
forall a. Semigroup a => a -> a -> a
<> Target -> [Text]
forall a. CmdArgs a => a -> [Text]
cmdArgs Target
target)
  NewWindow WindowParams
params ->
    Text -> [Text] -> Maybe TmuxQuery -> TmuxRequest
TmuxRequest Text
"new-window" (WindowParams -> [Text]
forall a. CmdArgs a => a -> [Text]
cmdArgs WindowParams
params)
  SplitWindow WindowParams
wParams SplitWindowParams
sParams ->
    Text -> [Text] -> Maybe TmuxQuery -> TmuxRequest
TmuxRequest Text
"split-window" (WindowParams -> [Text]
forall a. CmdArgs a => a -> [Text]
cmdArgs WindowParams
wParams [Text] -> [Text] -> [Text]
forall a. Semigroup a => a -> a -> a
<> SplitWindowParams -> [Text]
forall a. CmdArgs a => a -> [Text]
cmdArgs SplitWindowParams
sParams)
  SelectWindow SelectWindowParams
params ->
    Text -> [Text] -> Maybe TmuxQuery -> TmuxRequest
TmuxRequest Text
"select-window" (SelectWindowParams -> [Text]
forall a. CmdArgs a => a -> [Text]
cmdArgs SelectWindowParams
params)
  NewSession SessionParams
params ->
    Text -> [Text] -> Maybe TmuxQuery -> TmuxRequest
TmuxRequest Text
"new-session" (SessionParams -> [Text]
forall a. CmdArgs a => a -> [Text]
cmdArgs SessionParams
params)
  CopyMode CopyModeParams
params ->
    Text -> [Text] -> Maybe TmuxQuery -> TmuxRequest
TmuxRequest Text
"copy-mode" (CopyModeParams -> [Text]
forall a. CmdArgs a => a -> [Text]
cmdArgs CopyModeParams
params)
  SendKeys SendKeysParams
params ->
    Text -> [Text] -> Maybe TmuxQuery -> TmuxRequest
TmuxRequest Text
"send-keys" (SendKeysParams -> [Text]
forall a. CmdArgs a => a -> [Text]
cmdArgs SendKeysParams
params)
  SelectPane SelectParams
params ->
    Text -> [Text] -> Maybe TmuxQuery -> TmuxRequest
TmuxRequest Text
"select-pane" (SelectParams -> [Text]
forall a. CmdArgs a => a -> [Text]
cmdArgs SelectParams
params)
  KillPane KillPaneParams
params ->
    Text -> [Text] -> Maybe TmuxQuery -> TmuxRequest
TmuxRequest Text
"kill-pane" (KillPaneParams -> [Text]
forall a. CmdArgs a => a -> [Text]
cmdArgs KillPaneParams
params)
  MovePane JoinPaneParams
params ->
    Text -> [Text] -> Maybe TmuxQuery -> TmuxRequest
TmuxRequest Text
"move-pane" (JoinPaneParams -> [Text]
forall a. CmdArgs a => a -> [Text]
cmdArgs JoinPaneParams
params)
  ResizePane ResizePaneParams
params ->
    Text -> [Text] -> Maybe TmuxQuery -> TmuxRequest
TmuxRequest Text
"resize-pane" (ResizePaneParams -> [Text]
forall a. CmdArgs a => a -> [Text]
cmdArgs ResizePaneParams
params)
  PipePane PipePaneParams
params ->
    Text -> [Text] -> Maybe TmuxQuery -> TmuxRequest
TmuxRequest Text
"pipe-pane" (PipePaneParams -> [Text]
forall a. CmdArgs a => a -> [Text]
cmdArgs PipePaneParams
params)
  CapturePane CapturePaneParams
params ->
    Text -> [Text] -> Maybe TmuxQuery -> TmuxRequest
TmuxRequest Text
"capture-pane" (CapturePaneParams -> [Text]
forall a. CmdArgs a => a -> [Text]
cmdArgs CapturePaneParams
params)
  TmuxCommand a
KillServer ->
    Text -> [Text] -> Maybe TmuxQuery -> TmuxRequest
TmuxRequest Text
"kill-server" []

encode :: TmuxCommand a -> TmuxRequest
encode :: forall a. TmuxCommand a -> TmuxRequest
encode TmuxCommand a
cmd =
  TmuxCommand a -> Maybe TmuxQuery -> TmuxRequest
forall a. TmuxCommand a -> Maybe TmuxQuery -> TmuxRequest
request TmuxCommand a
cmd (TmuxCommand a -> Maybe TmuxQuery
forall a. TmuxCommand a -> Maybe TmuxQuery
query TmuxCommand a
cmd)

decode :: TmuxResponse -> TmuxCommand a -> Either DecodeError a
decode :: forall a. TmuxResponse -> TmuxCommand a -> Either DecodeError a
decode (TmuxResponse [Text]
out) = \case
  Fmap a -> a
f TmuxCommand a
cmd ->
    a -> a
f (a -> a) -> Either DecodeError a -> Either DecodeError a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TmuxResponse -> TmuxCommand a -> Either DecodeError a
forall a. TmuxResponse -> TmuxCommand a -> Either DecodeError a
decode ([Text] -> TmuxResponse
TmuxResponse [Text]
out) TmuxCommand a
cmd
  ListPanes PaneSelection
_ ->
    [Text] -> Either DecodeError [Pane]
forall a. TmuxCodec a => [Text] -> Either DecodeError [a]
multi [Text]
out
  ListWindows WindowSelection
_ ->
    [Text] -> Either DecodeError [Window]
forall a. TmuxCodec a => [Text] -> Either DecodeError [a]
multi [Text]
out
  TmuxCommand a
ListSessions ->
    [Text] -> Either DecodeError [Session]
forall a. TmuxCodec a => [Text] -> Either DecodeError [a]
multi [Text]
out
  TmuxCommand a
ListClients ->
    [Text] -> Either DecodeError [Client]
forall a. TmuxCodec a => [Text] -> Either DecodeError [a]
multi [Text]
out
  SwitchClient ClientId
_ Target
_ ->
    Either DecodeError a
Either DecodeError ()
forall (f :: * -> *). Applicative f => f ()
unit
  NewWindow WindowParams
_ ->
    [Text] -> Either DecodeError a
forall a. TmuxCodec a => [Text] -> Either DecodeError a
single [Text]
out
  SplitWindow WindowParams
_ SplitWindowParams
_ ->
    [Text] -> Either DecodeError a
forall a. TmuxCodec a => [Text] -> Either DecodeError a
single [Text]
out
  SelectWindow SelectWindowParams
_ ->
    Either DecodeError a
Either DecodeError ()
forall (f :: * -> *). Applicative f => f ()
unit
  NewSession SessionParams
_ ->
    [Text] -> Either DecodeError a
forall a. TmuxCodec a => [Text] -> Either DecodeError a
single [Text]
out
  CopyMode CopyModeParams
_ ->
    Either DecodeError a
Either DecodeError ()
forall (f :: * -> *). Applicative f => f ()
unit
  SendKeys SendKeysParams
_ ->
    Either DecodeError a
Either DecodeError ()
forall (f :: * -> *). Applicative f => f ()
unit
  SelectPane SelectParams
_ ->
    Either DecodeError a
Either DecodeError ()
forall (f :: * -> *). Applicative f => f ()
unit
  KillPane KillPaneParams
_ ->
    Either DecodeError a
Either DecodeError ()
forall (f :: * -> *). Applicative f => f ()
unit
  MovePane JoinPaneParams
_ ->
    Either DecodeError a
Either DecodeError ()
forall (f :: * -> *). Applicative f => f ()
unit
  ResizePane ResizePaneParams
_ ->
    Either DecodeError a
Either DecodeError ()
forall (f :: * -> *). Applicative f => f ()
unit
  PipePane PipePaneParams
_ ->
    Either DecodeError a
Either DecodeError ()
forall (f :: * -> *). Applicative f => f ()
unit
  CapturePane CapturePaneParams {Bool
$sel:stripBlank:CapturePaneParams :: CapturePaneParams -> Bool
stripBlank :: Bool
stripBlank, Bool
$sel:stripTrailingWs:CapturePaneParams :: CapturePaneParams -> Bool
stripTrailingWs :: Bool
stripTrailingWs} ->
    a -> Either DecodeError a
forall a. a -> Either DecodeError a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a -> Either DecodeError a) -> a -> Either DecodeError a
forall a b. (a -> b) -> a -> b
$
    Bool -> (a -> a) -> a -> a
forall a. Bool -> (a -> a) -> a -> a
applyWhen Bool
stripBlank ((Text -> Bool) -> [Text] -> [Text]
forall a. (a -> Bool) -> [a] -> [a]
dropWhileEnd (Text
"" ==)) (a -> a) -> a -> a
forall a b. (a -> b) -> a -> b
$
    Bool -> ([Text] -> [Text]) -> [Text] -> [Text]
forall a. Bool -> (a -> a) -> a -> a
applyWhen Bool
stripTrailingWs ((Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Text
Text.stripEnd) ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$
    [Text]
out
  TmuxCommand a
KillServer ->
    Either DecodeError a
Either DecodeError ()
forall (f :: * -> *). Applicative f => f ()
unit