Skip to content

Commit

Permalink
tmux-mate init command (#25)
Browse files Browse the repository at this point in the history
* Init command

* Default to tmux-mate.dhall if nothing else passed

* Start command

* Update readme
  • Loading branch information
danieljharvey committed Jun 6, 2020
1 parent fa1d863 commit 126ce03
Show file tree
Hide file tree
Showing 7 changed files with 117 additions and 24 deletions.
9 changes: 9 additions & 0 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,15 @@ brew update && brew install danieljharvey/tools/tmux-mate

Binaries available on the [releases](https://github.com/danieljharvey/tmux-mate/releases) page.

### Getting started

```bash
# create a default tmux-mate.dhall
tmux-mate init
# Start running everything
tmux-mate start
```

### Tutorial

Let's grab a couple of sample config files...
Expand Down
7 changes: 7 additions & 0 deletions app/CLICommands.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,7 @@
module CLICommands where

import TmuxMate (CLIOptions (..))

data CLICommand
= CLIRun CLIOptions
| CLIInit
35 changes: 13 additions & 22 deletions app/Main.hs
Original file line number Diff line number Diff line change
@@ -1,29 +1,20 @@
module Main where

import Options.Applicative
import CLICommands
import Options (command)
import qualified Options.Applicative as Opt
import System.Exit
import TmuxMate

main :: IO ()
main = do
options' <- execParser (info options fullDesc)
didItWork <- loadTestSession options'
case didItWork of
Yeah -> exitWith ExitSuccess
Nah i -> exitWith (ExitFailure i)

configFilePathParser :: Parser ConfigFilePath
configFilePathParser =
ConfigFilePath
<$> argument str (metavar "<path-to-config-file>")

verbosityParser :: Parser Verbosity
verbosityParser =
flag' Chatty (short 'v' <> long "verbose")
<|> flag' DryRun (short 'd' <> long "dry-run")
<|> pure Silent

options :: Parser CLIOptions
options =
CLIOptions
<$> configFilePathParser <*> verbosityParser
command' <- Opt.execParser (Opt.info command Opt.fullDesc)
case command' of
CLIInit -> do
createTmuxMateDhall
putStrLn "Initial tmux-mate.dhall created!"
CLIRun options' -> do
didItWork <- loadTestSession options'
case didItWork of
Yeah -> exitWith ExitSuccess
Nah i -> exitWith (ExitFailure i)
46 changes: 46 additions & 0 deletions app/Options.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,46 @@
module Options (command) where

import CLICommands
import Options.Applicative ((<|>))
import qualified Options.Applicative as Opt
import TmuxMate

command :: Opt.Parser CLICommand
command =
otherCommands
<|> (CLIRun <$> options)

configFilePathParser :: Opt.Parser (Maybe ConfigFilePath)
configFilePathParser =
( Just <$> ConfigFilePath
<$> Opt.argument Opt.str (Opt.metavar "<path-to-config-file>")
)
<|> pure Nothing

verbosityParser :: Opt.Parser Verbosity
verbosityParser =
Opt.flag' Chatty (Opt.short 'v' <> Opt.long "verbose")
<|> Opt.flag' DryRun (Opt.short 'd' <> Opt.long "dry-run")
<|> pure Silent

options :: Opt.Parser CLIOptions
options =
CLIOptions
<$> configFilePathParser <*> verbosityParser

otherCommands :: Opt.Parser CLICommand
otherCommands =
Opt.subparser
( Opt.command
"init"
( Opt.info
(pure CLIInit)
(Opt.progDesc "Initialise a new tmux-mate.dhall file")
)
<> Opt.command
"start"
( Opt.info
(CLIRun <$> options)
(Opt.progDesc "Start running everything in the selected config file")
)
)
5 changes: 4 additions & 1 deletion src/TmuxMate.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,12 +7,15 @@ module TmuxMate
CLIOptions (..),
ConfigFilePath (..),
Verbosity (..),
createTmuxMateDhall,
)
where

import Data.Maybe (fromMaybe)
import qualified Dhall as Dhall
import System.Process
import TmuxMate.Commands
import TmuxMate.Init
import TmuxMate.Logger
import TmuxMate.Running
import TmuxMate.TmuxCommands
Expand All @@ -36,7 +39,7 @@ data DidItWork
loadTestSession :: CLIOptions -> IO DidItWork
loadTestSession options = do
let (decoder :: Dhall.Decoder Session) = Dhall.auto
let path = getConfigFilePath $ configFilePath options
let path = fromMaybe "tmux-mate.dhall" (getConfigFilePath <$> configFilePath options)
myLog = logger (verbosity options)
config <- Dhall.detailed (Dhall.inputFile decoder path)
case parseSession config of
Expand Down
37 changes: 37 additions & 0 deletions src/TmuxMate/Init.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,37 @@
module TmuxMate.Init (createTmuxMateDhall) where

-- where we make a new empty session file

import Data.Text.IO
import Dhall
import Dhall.Core (pretty)
import TmuxMate.Types
( Pane (..),
PaneArrangement (..),
PaneCommand (..),
Session (..),
SessionName (..),
Window (..),
WindowName (..),
)

createTmuxMateDhall :: IO ()
createTmuxMateDhall = do
let dhallVal = pretty (embed inject defaultSession)
Data.Text.IO.writeFile "./tmux-mate.dhall" dhallVal

defaultSession :: Session
defaultSession =
Session
(SessionName "tmux-mate")
[ Window
(WindowName "first")
[ Pane
( PaneCommand "watch echo \"hello from tmux-mate\""
),
Pane
( PaneCommand "watch echo \"hello again from tmux-mate\""
)
]
(PaneArrangement "tiled")
]
2 changes: 1 addition & 1 deletion src/TmuxMate/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -166,7 +166,7 @@ newtype ConfigFilePath

data CLIOptions
= CLIOptions
{ configFilePath :: ConfigFilePath,
{ configFilePath :: Maybe ConfigFilePath,
verbosity :: Verbosity
}
deriving (Eq, Ord, Show)

0 comments on commit 126ce03

Please # to comment.