use KeyName list instead of AttrPath list

This commit is contained in:
Allen Nelson 2016-01-24 18:01:45 -06:00
parent 80a7dcb684
commit f04ccf9476
4 changed files with 42 additions and 40 deletions

View file

@ -28,47 +28,47 @@ import Prelude hiding (readFile, concat, concatMap, elem, mapM,
-- them. The actual 'NExpr' type is a fixed point of this functor, defined
-- below.
data NExprF r
= NConstant NAtom
= NConstant !NAtom
-- ^ Constants: ints, bools, URIs, and null.
| NStr (NString r)
| NStr !(NString r)
-- ^ A string, with interpolated expressions.
| NSym Text
| NSym !Text
-- ^ A variable. For example, in the expression @f a@, @f@ is represented
-- as @NSym "f"@ and @a@ as @NSym "a"@.
| NList [r]
| NList ![r]
-- ^ A list literal.
| NSet [Binding r]
| NSet ![Binding r]
-- ^ An attribute set literal, not recursive.
| NRecSet [Binding r]
| NRecSet ![Binding r]
-- ^ An attribute set literal, recursive.
| NLiteralPath FilePath
| NLiteralPath !FilePath
-- ^ A path expression, which is evaluated to a store path. The path here
-- can be relative, in which case it's evaluated relative to the file in
-- which it appears.
| NEnvPath FilePath
| NEnvPath !FilePath
-- ^ A path which refers to something in the Nix search path (the NIX_PATH
-- environment variable. For example, @<nixpkgs/pkgs>@.
| NUnary NUnaryOp r
| NUnary !NUnaryOp !r
-- ^ Application of a unary operator to an expression.
| NBinary NBinaryOp r r
| NBinary !NBinaryOp !r !r
-- ^ Application of a binary operator to two expressions.
| NSelect r (NAttrPath r) (Maybe r)
| NSelect !r !(NAttrPath r) !(Maybe r)
-- ^ Dot-reference into an attribute set, optionally providing an
-- alternative if the key doesn't exist.
| NHasAttr r (NAttrPath r)
| NHasAttr !r !(NAttrPath r)
-- ^ Ask if a set contains a given attribute path.
| NAbs (Params r) r
| NAbs !(Params r) !r
-- ^ A function literal (lambda abstraction).
| NApp r r
| NApp !r !r
-- ^ Apply a function to an argument.
| NLet [Binding r] r
| NLet ![Binding r] !r
-- ^ Evaluate the second argument after introducing the bindings.
| NIf r r r
| NIf !r !r !r
-- ^ If-then-else statement.
| NWith r r
| NWith !r !r
-- ^ Evaluate an attribute set, bring its bindings into scope, and
-- evaluate the second argument.
| NAssert r r
| NAssert !r !r
-- ^ Assert that the first returns true before evaluating the second.
deriving (Ord, Eq, Generic, Typeable, Data, Functor, Show)
@ -81,20 +81,20 @@ type NExpr = Fix NExprF
data NAtom
-- | An integer. The c nix implementation currently only supports
-- integers that fit in the range of 'Int64'.
= NInt Integer
= NInt !Integer
-- | Booleans.
| NBool Bool
| NBool !Bool
-- | Null values. There's only one of this variant.
| NNull
-- | URIs, which are just string literals, but do not need quotes.
| NUri Text
| NUri !Text
deriving (Eq, Ord, Generic, Typeable, Data, Show)
-- | A single line of the bindings section of a let expression or of a set.
data Binding r
= NamedVar (NAttrPath r) r
= NamedVar !(NAttrPath r) !r
-- ^ An explicit naming, such as @x = y@ or @x.y = z@.
| Inherit (Maybe r) [NAttrPath r]
| Inherit !(Maybe r) ![NKeyName r]
-- ^ Using a name already in scope, such as @inherit x;@ which is shorthand
-- for @x = x;@ or @inherit (x) y;@ which means @y = x.y;@.
deriving (Typeable, Data, Ord, Eq, Functor, Show)
@ -102,9 +102,9 @@ data Binding r
-- | @Params@ represents all the ways the formal parameters to a
-- function can be represented.
data Params r
= Param Text
= Param !Text
-- ^ For functions with a single named argument, such as @x: x + 1@.
| ParamSet (ParamSet r) (Maybe Text)
| ParamSet !(ParamSet r) !(Maybe Text)
-- ^ Explicit parameters (argument must be a set). Might specify a name
-- to bind to the set in the function body.
deriving (Ord, Eq, Generic, Typeable, Data, Functor, Show,
@ -112,27 +112,27 @@ data Params r
-- | An explicit parameter set; provides a shorthand for unpacking arguments.
data ParamSet r
= FixedParamSet (Map Text (Maybe r))
= FixedParamSet !(Map Text (Maybe r))
-- ^ A fixed set, where no arguments beyond what is specified in the map
-- may be given. The map might contain defaults for arguments not passed.
| VariadicParamSet (Map Text (Maybe r))
| VariadicParamSet !(Map Text (Maybe r))
-- ^ Same as the 'FixedParamSet', but extra arguments are allowed.
deriving (Ord, Eq, Generic, Typeable, Data, Functor, Show,
Foldable, Traversable)
-- | 'Antiquoted' represents an expression that is either
-- antiquoted (surrounded by ${...}) or plain (not antiquoted).
data Antiquoted v r = Plain v | Antiquoted r
data Antiquoted v r = Plain !v | Antiquoted !r
deriving (Ord, Eq, Generic, Typeable, Data, Functor, Show)
-- | An 'NString' is a list of things that are either a plain string
-- or an antiquoted expression. After the antiquotes have been evaluated,
-- the final string is constructed by concating all the parts.
data NString r
= DoubleQuoted [Antiquoted Text r]
= DoubleQuoted ![Antiquoted Text r]
-- ^ Strings wrapped with double-quotes (") are not allowed to contain
-- literal newline characters.
| Indented [Antiquoted Text r]
| Indented ![Antiquoted Text r]
-- ^ Strings wrapped with two single quotes ('') can contain newlines,
-- and their indentation will be stripped.
deriving (Eq, Ord, Generic, Typeable, Data, Functor, Show)
@ -162,8 +162,8 @@ instance IsString (NString r) where
-- allowed even if the context requires a static keyname, but the
-- parser still considers it a 'DynamicKey' for simplicity.
data NKeyName r
= DynamicKey (Antiquoted (NString r) r)
| StaticKey Text
= DynamicKey !(Antiquoted (NString r) r)
| StaticKey !Text
deriving (Eq, Ord, Generic, Typeable, Data, Show)
-- | Deriving this instance automatically is not possible because @r@

View file

@ -230,8 +230,9 @@ argExpr = choice [atLeft, onlyname, atRight] <* symbolic ':' where
nixBinders :: Parser [Binding NExpr]
nixBinders = (inherit <|> namedVar) `endBy` symbolic ';' where
inherit = Inherit <$> (reserved "inherit" *> optional scope) <*> many ((:[]) <$> keyName)
<?> "inherited binding"
inherit = Inherit <$> (reserved "inherit" *> optional scope)
<*> many (keyName)
<?> "inherited binding"
namedVar = NamedVar <$> nixSelector <*> (symbolic '=' *> nixExpr)
<?> "variable binding"
scope = parens nixExpr <?> "inherit scope"

View file

@ -93,7 +93,7 @@ prettyParamSet params = lbrace <+> middle <+> rbrace
prettyBind :: Binding NixDoc -> Doc
prettyBind (NamedVar n v) = prettySelector n <+> equals <+> withoutParens v <> semi
prettyBind (Inherit s ns)
= text "inherit" <+> scope <> fillSep (map prettySelector ns) <> semi
= text "inherit" <+> scope <> fillSep (map prettyKeyName ns) <> semi
where scope = maybe empty ((<> space) . parens . withoutParens) s
prettyKeyName :: NKeyName NixDoc -> Doc

View file

@ -70,15 +70,15 @@ case_set_inherit :: Assertion
case_set_inherit = do
assertParseString "{ e = 3; inherit a b; }" $ Fix $ NSet
[ NamedVar (mkSelector "e") $ mkInt 3
, Inherit Nothing [mkSelector "a", mkSelector "b"]
, Inherit Nothing $ StaticKey <$> ["a", "b"]
]
assertParseString "{ inherit; }" $ Fix $ NSet [ Inherit Nothing [] ]
case_set_scoped_inherit :: Assertion
case_set_scoped_inherit = assertParseString "{ inherit (a) b c; e = 4; inherit(a)b c; }" $ Fix $ NSet
[ Inherit (Just (mkSym "a")) [mkSelector "b", mkSelector "c"]
[ Inherit (Just (mkSym "a")) $ StaticKey <$> ["b", "c"]
, NamedVar (mkSelector "e") $ mkInt 4
, Inherit (Just (mkSym "a")) [mkSelector "b", mkSelector "c"]
, Inherit (Just (mkSym "a")) $ StaticKey <$> ["b", "c"]
]
case_set_rec :: Assertion
@ -111,7 +111,7 @@ case_set_inherit_direct = assertParseString "{ inherit ({a = 3;}); }" $ Fix $ NS
case_inherit_selector :: Assertion
case_inherit_selector = do
assertParseString "{ inherit \"a\"; }" $ Fix $ NSet
[ Inherit Nothing [ [DynamicKey (Plain "a")] ] ]
[Inherit Nothing [DynamicKey (Plain "a")]]
assertParseFail "{ inherit a.x; }"
case_int_list :: Assertion
@ -193,7 +193,8 @@ case_nested_let = do
case_let_scoped_inherit :: Assertion
case_let_scoped_inherit = do
assertParseString "let a = null; inherit (b) c; in c" $ Fix $ NLet
[ NamedVar (mkSelector "a") mkNull, Inherit (Just $ mkSym "b") [mkSelector "c"] ]
[ NamedVar (mkSelector "a") mkNull
, Inherit (Just $ mkSym "b") [StaticKey "c"] ]
(mkSym "c")
assertParseFail "let inherit (b) c in c"