Add support for the --attr/-A option

This commit is contained in:
John Wiegley 2018-04-11 21:31:48 -07:00
parent 90e4a3ec37
commit 371380c98f
2 changed files with 75 additions and 15 deletions

View file

@ -1,6 +1,8 @@
{-# LANGUAGE LambdaCase #-} {-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiWayIf #-} {-# LANGUAGE MultiWayIf #-}
-- {-# LANGUAGE QuasiQuotes #-} -- {-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ViewPatterns #-}
module Main where module Main where
@ -11,7 +13,9 @@ import Control.Monad
import Control.Monad.ST import Control.Monad.ST
import Data.Fix import Data.Fix
import qualified Data.HashMap.Lazy as M import qualified Data.HashMap.Lazy as M
import qualified Data.Text as Text
import qualified Data.Text.IO as Text import qualified Data.Text.IO as Text
import qualified Data.Text.Read as Text
import qualified Nix import qualified Nix
import Nix.Cache import Nix.Cache
import Nix.Exec (Lazy, runLazyM) import Nix.Exec (Lazy, runLazyM)
@ -91,19 +95,49 @@ main = do
runLazyM $ normalForm =<< g argmap runLazyM $ normalForm =<< g argmap
_ -> pure f _ -> pure f
result h = case attr opts of
Nothing -> h
Just (Text.splitOn "." -> keys) -> go keys
where
go [] v = h v
go ((Text.decimal -> Right (n,_)):ks) v = case v of
Fix (V.NVList xs) -> case ks of
[] -> h (xs !! n)
_ -> go ks (xs !! n)
_ -> errorWithoutStackTrace $
"Expected a list for selector '" ++ show n
++ "', but got: " ++ show v
go (k:ks) v = case v of
Fix (V.NVSet xs _) ->
case M.lookup k xs of
Nothing ->
errorWithoutStackTrace $
"Set does not contain key '"
++ Text.unpack k ++ "'"
Just v' -> case ks of
[] -> h v'
_ -> go ks v'
_ -> errorWithoutStackTrace $
"Expected a set for selector '" ++ Text.unpack k
++ "', but got: " ++ show v
if | evaluate opts, debug opts -> if | evaluate opts, debug opts ->
compute Nix.tracingEvalLoc expr print compute Nix.tracingEvalLoc expr (result print)
| evaluate opts, not (null args) -> | evaluate opts, not (null args) ->
compute Nix.evalLoc expr (putStrLn . printNix) compute Nix.evalLoc expr (result (putStrLn . printNix))
| evaluate opts -> | evaluate opts ->
putStrLn . printNix =<< Nix.evalLoc mpath expr result (putStrLn . printNix) =<< Nix.evalLoc mpath expr
| debug opts ->
print $ stripAnnotation expr | debug opts -> print $ stripAnnotation expr
| cache opts, Just path <- mpath -> do | cache opts, Just path <- mpath -> do
let file = addExtension (dropExtension path) "nixc" let file = addExtension (dropExtension path) "nixc"
writeCache file expr writeCache file expr
| parseOnly opts ->
void $ Exc.evaluate $ force expr | parseOnly opts -> void $ Exc.evaluate $ force expr
| otherwise -> | otherwise ->
displayIO stdout displayIO stdout
. renderPretty 0.4 80 . renderPretty 0.4 80

View file

@ -9,12 +9,18 @@ import Text.PrettyPrint.ANSI.Leijen hiding ((<$>))
data Options = Options data Options = Options
{ verbose :: Bool { verbose :: Bool
, debug :: Bool , debug :: Bool
, parse :: Bool
, parseOnly :: Bool
, findFile :: Maybe FilePath
, strict :: Bool
, evaluate :: Bool , evaluate :: Bool
-- , json :: Bool
-- , xml :: Bool
, attr :: Maybe Text
, include :: Maybe FilePath
, check :: Bool , check :: Bool
, readFrom :: Maybe FilePath , readFrom :: Maybe FilePath
, cache :: Bool , cache :: Bool
, parse :: Bool
, parseOnly :: Bool
, ignoreErrors :: Bool , ignoreErrors :: Bool
, expression :: Maybe Text , expression :: Maybe Text
, arg :: [(Text, Text)] , arg :: [(Text, Text)]
@ -40,9 +46,35 @@ nixOptions = Options
( short 'd' ( short 'd'
<> long "debug" <> long "debug"
<> help "Debug output") <> help "Debug output")
<*> switch
( long "parse"
<> help "Whether to parse the file (also the default right now)")
<*> switch
( long "parse-only"
<> help "Whether to parse only, no pretty printing or checking")
<*> optional (strOption
( long "find-file"
<> help "Look up the given files in Nix's search path"))
<*> switch
( long "strict"
<> help "When used with --eval, recursively evaluate list elements and attributes")
<*> switch <*> switch
( long "eval" ( long "eval"
<> help "Whether to evaluate, or just pretty-print") <> help "Whether to evaluate, or just pretty-print")
-- <*> switch
-- ( long "json"
-- <> help "Print the resulting value as an JSON representation of the abstract syntax tree")
-- <*> switch
-- ( long "xml"
-- <> help "Print the resulting value as an XML representation of the abstract syntax tree")
<*> optional (strOption
( short 'A'
<> long "attr"
<> help "Select an attribute from the top-level Nix expression being evaluated"))
<*> optional (strOption
( short 'I'
<> long "include"
<> help "Add a path to the Nix expression search path"))
<*> switch <*> switch
( long "check" ( long "check"
<> help "Whether to check for syntax errors after parsing") <> help "Whether to check for syntax errors after parsing")
@ -52,12 +84,6 @@ nixOptions = Options
<*> switch <*> switch
( long "cache" ( long "cache"
<> help "Write out the parsed expression tree to a binary cache") <> help "Write out the parsed expression tree to a binary cache")
<*> switch
( long "parse"
<> help "Whether to parse the file (also the default right now)")
<*> switch
( long "parse-only"
<> help "Whether to parse only, no pretty printing or checking")
<*> switch <*> switch
( long "ignore-errors" ( long "ignore-errors"
<> help "Continue parsing files, even if there are errors") <> help "Continue parsing files, even if there are errors")