Skip to content

Commit

Permalink
Rename Placeholder fields => format
Browse files Browse the repository at this point in the history
  • Loading branch information
myme committed May 19, 2024
1 parent e0e779c commit d9bfb7c
Show file tree
Hide file tree
Showing 6 changed files with 15 additions and 15 deletions.
2 changes: 1 addition & 1 deletion src/Nixon.hs
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,7 @@ import Nixon.Language (Language (..), fromFilePath)
import Nixon.Logging (log_error, log_info)
import Nixon.Prelude
import Nixon.Process (run)
import Nixon.Project (Project, project_path, inspectProjects)
import Nixon.Project (Project, inspectProjects, project_path)
import qualified Nixon.Project as P
import Nixon.Select (Candidate (..), Selection (..), SelectionType (..))
import qualified Nixon.Select as Select
Expand Down
6 changes: 3 additions & 3 deletions src/Nixon/Command/Placeholder.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
module Nixon.Command.Placeholder
( Placeholder (..),
PlaceholderFields (..),
PlaceholderFormat (..),
PlaceholderType (..)
)
where
Expand All @@ -10,7 +10,7 @@ import Nixon.Prelude
data PlaceholderType = Arg | EnvVar {_envName :: Text} | Stdin
deriving (Eq, Show)

data PlaceholderFields
data PlaceholderFormat
= -- | Interpret output as columns and extract the specified columns
Columns [Int]
| -- | Interpret output as fields and extract the specified fields
Expand All @@ -28,7 +28,7 @@ data Placeholder = Placeholder
-- | The command it's referencing
name :: Text,
-- | The field numbers to extract
fields :: PlaceholderFields,
format :: PlaceholderFormat,
-- | If the placeholder can select multiple
multiple :: Bool,
-- | Pre-expanded value of the placeholder
Expand Down
8 changes: 4 additions & 4 deletions src/Nixon/Command/Run.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,7 @@ import Nixon.Process (run_with_output)
import qualified Nixon.Process
import Nixon.Project (Project)
import qualified Nixon.Project as Project
import Nixon.Select (Selection (..), Selector, selector_fields, selector_multiple)
import Nixon.Select (Selection (..), Selector, selector_format, selector_multiple)
import qualified Nixon.Select as Select
import Nixon.Types (Nixon)
import Nixon.Utils (shell_to_list, toLines)
Expand Down Expand Up @@ -63,13 +63,13 @@ zipArgs (p : ps) (a : as) = (p, Select.search a) : zipArgs ps as
resolveEnv' :: Project -> Selector Nixon -> [(P.Placeholder, Select.SelectorOpts)] -> Nixon (Maybe (Shell Text), [Text], Nixon.Process.Env)
resolveEnv' project selector = foldM resolveEach (Nothing, [], [])
where
resolveEach (stdin, args', envs) (P.Placeholder envType cmdName fields multiple value, select_opts) = do
resolveEach (stdin, args', envs) (P.Placeholder envType cmdName format' multiple value, select_opts) = do
resolved <- case value of
[] -> do
cmd' <- assertCommand cmdName
let select_opts' =
select_opts
{ selector_fields = fields,
{ selector_format = format',
selector_multiple = Just multiple
}
resolveCmd project selector cmd' select_opts'
Expand Down Expand Up @@ -97,7 +97,7 @@ resolveCmd project selector cmd select_opts = do
let projectPath = Just (Project.project_path project)
linesEval <- getEvaluator (run_with_output stream) cmd args projectPath env' (toLines <$> stdin)
jsonEval <- getEvaluator (run_with_output BS.stream) cmd args projectPath env' (BS.fromUTF8 <$> stdin)
selection <- selector select_opts $ case select_opts.selector_fields of
selection <- selector select_opts $ case select_opts.selector_format of
P.Columns cols -> do
let parseColumns' = map T.unwords . pickColumns cols . parseColumns
(title, value) <- (drop 1 &&& parseColumns') . map lineToText <$> shell_to_list linesEval
Expand Down
8 changes: 4 additions & 4 deletions src/Nixon/Config/Markdown.hs
Original file line number Diff line number Diff line change
Expand Up @@ -367,7 +367,7 @@ parsePlaceholderModifiers placeholder = do
parsePipeFields p =
(P.string "cols" *> P.many P.space *> parseFields P.Columns p)
<|> (P.string "fields" *> P.many P.space *> parseFields P.Fields p)
<|> (P.string "json" $> p {P.fields = P.JSON})
<|> (P.string "json" $> p {P.format = P.JSON})

parsePipeMultiple p = (P.string "multi" :: Parser String) $> p {P.multiple = True}

Expand All @@ -378,11 +378,11 @@ parsePlaceholderModifiers placeholder = do
-- Accept fields and multiple in any order
(parseFields P.Fields p >>= perhaps parseMultiple) <|> (parseMultiple p >>= perhaps (parseFields P.Fields))

parseFields :: ([Int] -> P.PlaceholderFields) -> P.Placeholder -> Parser P.Placeholder
parseFields :: ([Int] -> P.PlaceholderFormat) -> P.Placeholder -> Parser P.Placeholder
parseFields fieldType p' = do
fields <- mapMaybe readMaybe <$> (P.many1 P.digit `P.sepBy1` P.char ',')
when (p'.fields /= P.Lines) $ fail "Placeholder format already set"
pure $ p' {P.fields = fieldType fields}
when (p'.format /= P.Lines) $ fail "Placeholder format already set"
pure $ p' {P.format = fieldType fields}

parseMultiple :: P.Placeholder -> Parser P.Placeholder
parseMultiple p' = do
Expand Down
4 changes: 2 additions & 2 deletions src/Nixon/Select.hs
Original file line number Diff line number Diff line change
Expand Up @@ -84,7 +84,7 @@ instance Functor Selection where
data SelectorOpts = SelectorOpts
{ selector_title :: Maybe Text,
selector_search :: Maybe Text,
selector_fields :: Cmd.PlaceholderFields,
selector_format :: Cmd.PlaceholderFormat,
selector_multiple :: Maybe Bool
}

Expand All @@ -93,7 +93,7 @@ defaults =
SelectorOpts
{ selector_title = Nothing,
selector_search = Nothing,
selector_fields = Cmd.Lines,
selector_format = Cmd.Lines,
selector_multiple = Nothing
}

Expand Down
2 changes: 1 addition & 1 deletion test/Test/Nixon/Config/Markdown.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ import Control.Arrow ((&&&))
import Data.Either (isLeft)
import qualified Data.Text as T
import qualified Nixon.Command as Cmd
import Nixon.Command.Placeholder (Placeholder (..), PlaceholderFields (..), PlaceholderType (..))
import Nixon.Command.Placeholder (Placeholder (..), PlaceholderFormat (..), PlaceholderType (..))
import Nixon.Config.Markdown (parseCommandName, parseHeaderArgs, parseMarkdown)
import Nixon.Config.Types (defaultConfig)
import qualified Nixon.Config.Types as Cfg
Expand Down

0 comments on commit d9bfb7c

Please sign in to comment.