Skip to content

Commit

Permalink
cli: Add --insert
Browse files Browse the repository at this point in the history
Ouputs a (project) command source on stdout. Intended to fill a prompt
with a command source.
  • Loading branch information
myme committed May 10, 2024
1 parent 2855911 commit bf71c2c
Show file tree
Hide file tree
Showing 3 changed files with 40 additions and 16 deletions.
13 changes: 11 additions & 2 deletions extra/nixon-widget.bash
Original file line number Diff line number Diff line change
@@ -1,10 +1,19 @@
nixon-widget() {
nixon-insert-selection() {
local selected="$(nixon -b fzf -T run -s)"
READLINE_LINE="${READLINE_LINE:0:$READLINE_POINT}$selected${READLINE_LINE:$READLINE_POINT}"
READLINE_POINT=$(( READLINE_POINT + ${#selected} ))
}

bind -x '"\ei": "nixon-widget"'
bind -x '"\ei": "nixon-insert-selection"'

nixon-insert-command ()
{
local command="$(nixon -b fzf -T run -i)"
READLINE_LINE="${READLINE_LINE:0:$READLINE_POINT}$command${READLINE_LINE:$READLINE_POINT}";
READLINE_POINT=$(( READLINE_POINT + ${#command} ))
}

bind -x '"\eI": nixon-insert-command'

nixon-insert-project ()
{
Expand Down
37 changes: 24 additions & 13 deletions src/Nixon.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
{-# LANGUAGE OverloadedRecordDot #-}

module Nixon
( nixon,
nixonWithConfig,
Expand Down Expand Up @@ -82,7 +84,7 @@ listProjectCommands project query = do
Selection _ matching -> liftIO $ T.putStr (T.unlines matching)
_ -> log_error "No commands."

fail :: MonadIO m => NixonError -> m a
fail :: (MonadIO m) => NixonError -> m a
fail err = liftIO (throwIO err)

-- | Find and run a command in a project.
Expand All @@ -93,13 +95,13 @@ handleCmd project cmd opts = do
EmptySelection -> fail $ EmptyError "No command selected."
CanceledSelection -> fail $ EmptyError "Command selection canceled."
Selection _ [] -> fail $ EmptyError "No command selected."
Selection selectionType [cmd'] ->
if Opts.runSelect opts
then do
Selection selectionType [cmd']
| opts.runInsert -> liftIO $ T.putStrLn cmd'.cmdSource
| opts.runSelect -> do
let selectOpts = Select.defaults {Select.selector_multiple = Just True}
resolved <- Cmd.resolveCmd project selector cmd' selectOpts
printf (s % "\n") (T.unlines resolved)
else do
| otherwise -> do
case selectionType of
Select.Default -> Cmd.runCmd selector project cmd' (Opts.runArgs opts)
Select.Edit -> editCmd project cmd' (Opts.runArgs opts)
Expand Down Expand Up @@ -173,6 +175,7 @@ evalAction projects (EvalOpts source placeholders lang projSelect) = do
RunOpts
{ runCommand = Nothing,
runArgs = [],
runInsert = False,
runList = False,
runSelect = False
}
Expand Down Expand Up @@ -201,7 +204,13 @@ projectAction projects opts
then void . liftIO . for ps $ printf (fp % "\n") . project_path
else case ps of
[project] ->
let opts' = RunOpts (Opts.projCommand opts) (Opts.projArgs opts) (Opts.projList opts) (Opts.projSelect opts)
let opts' =
RunOpts
opts.projCommand
opts.projArgs
opts.projInsert
opts.projList
opts.projSelect
in findAndHandleCmd handleCmd project opts'
_ -> liftIO (throwIO $ NixonError "Multiple projects selected.")

Expand All @@ -226,12 +235,13 @@ getSortedProjects = do

-- If switching to a project takes a long time it would be nice to see a window
-- showing the progress of starting the environment.
nixonWithConfig :: MonadIO m => Config.Config -> m ()
nixonWithConfig :: (MonadIO m) => Config.Config -> m ()
nixonWithConfig userConfig = liftIO $ do
(sub_cmd, cfg) <- either die pure =<< Opts.parseArgs (nixonCompleter userConfig)

err <- try $
runNixon (userConfig <> cfg) $ do
err <- try
$ runNixon (userConfig <> cfg)
$ do
projects <- getSortedProjects
case sub_cmd of
EvalCommand evalOpts -> do
Expand All @@ -252,12 +262,13 @@ nixonWithConfig userConfig = liftIO $ do
Left (NixonError msg) -> die msg
Right _ -> pure ()

nixonCompleter :: MonadIO m => Config.Config -> CompletionType -> [String] -> m [String]
nixonCompleter :: (MonadIO m) => Config.Config -> CompletionType -> [String] -> m [String]
nixonCompleter userConfig compType args = do
let parse_args = Opts.parseArgs $ nixonCompleter userConfig
(_, cfg) <- liftIO $ either die pure =<< withArgs args parse_args
liftIO $
runNixon (userConfig <> cfg) $ do
liftIO
$ runNixon (userConfig <> cfg)
$ do
projects <- getSortedProjects
case compType of
Opts.Eval -> pure []
Expand All @@ -275,5 +286,5 @@ nixonCompleter userConfig compType args = do
pure $ map (T.unpack . cmdName) commands

-- | Nixon with default configuration
nixon :: MonadIO m => m ()
nixon :: (MonadIO m) => m ()
nixon = nixonWithConfig Config.defaultConfig
6 changes: 5 additions & 1 deletion src/Nixon/Config/Options.hs
Original file line number Diff line number Diff line change
Expand Up @@ -86,6 +86,7 @@ data ProjectOpts = ProjectOpts
{ projProject :: Maybe Text,
projCommand :: Maybe Text,
projArgs :: [Text],
projInsert :: Bool,
projList :: Bool,
projSelect :: Bool
}
Expand All @@ -94,6 +95,7 @@ data ProjectOpts = ProjectOpts
data RunOpts = RunOpts
{ runCommand :: Maybe Text,
runArgs :: [Text],
runInsert :: Bool,
runList :: Bool,
runSelect :: Bool
}
Expand Down Expand Up @@ -196,6 +198,7 @@ projectParser mkcompleter =
<> Opts.completer (mkcompleter Run)
)
<*> many (Opts.strArgument $ Opts.metavar "args..." <> Opts.help "Arguments to command")
<*> switch "insert" 'i' "Select a project command and output its source"
<*> switch "list" 'l' "List projects"
<*> switch "select" 's' "Select a project and output on stdout"

Expand All @@ -204,8 +207,9 @@ runParser completer =
RunOpts
<$> optional (Opts.strArgument $ Opts.metavar "command" <> Opts.help "Command to run" <> Opts.completer completer)
<*> many (Opts.strArgument $ Opts.metavar "args..." <> Opts.help "Arguments to command")
<*> switch "insert" 'i' "Select a command and output its source"
<*> switch "list" 'l' "List commands"
<*> switch "select" 's' "Select a command and output on stdout"
<*> switch "select" 's' "Output command selection on stdout"

-- | Read configuration from config file and command line arguments
parseArgs :: MonadIO m => (CompletionType -> Completer) -> m (Either ConfigError (SubCommand, Config))
Expand Down

0 comments on commit bf71c2c

Please sign in to comment.