Skip to content

Commit a6d9f3e

Browse files
committed
Expr: Types: Binding(Inherit): NKeyName -> VarName
Thread: #377 (comment) `inherit x y` in y` position always takes a variable name. Nix allows `inherit x "y"`, but there is no use (in the wild real life use) for it, it seems a misfeature and would be considered a quirk of the original type system/implementation, until the use case of it would be clear (which is hard, since there is a single use of it in Nixpkgs, which is mentioned in the thread).
1 parent f81830b commit a6d9f3e

File tree

11 files changed

+51
-53
lines changed

11 files changed

+51
-53
lines changed

ChangeLog.md

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,10 @@ Partial log (for now):
88
* Breaking:
99

1010
* `Nix.Expr.Shorthands`:
11-
* `inherit{,From}`: dropped second argument as irrelevant ([report](https://github.com/haskell-nix/hnix/issues/326)).
11+
* `inherit{,From}`:
12+
* dropped second(/third) argument as irrelevant ([report](https://github.com/haskell-nix/hnix/issues/326))
13+
* bindings to inherit changed type from complex `[NKeyName]` (which is for static & dynamic keys) to `[VarName]` (`VarName` is newtype of `Text`).
14+
* So examples of use now are: `inherit ["a", "b"]`, `inheritFrom (var "a") ["b", "c"]`
1215
* `mkAssert`: fixed ([report](https://github.com/haskell-nix/hnix/issues/969)).
1316
* fx presedence between the operators:
1417

src/Nix/Eval.hs

Lines changed: 19 additions & 28 deletions
Original file line numberDiff line numberDiff line change
@@ -369,36 +369,27 @@ evalBinds recursive binds =
369369
=<< evalSetterKeyName h
370370

371371
applyBindToAdt scopes (Inherit ms names pos) =
372-
catMaybes <$>
373-
traverse
374-
processScope
375-
names
372+
pure $ processScope <$> names
376373
where
377374
processScope
378-
:: NKeyName (m v)
379-
-> m (Maybe ([VarName], SourcePos, m v))
380-
processScope nkeyname =
381-
(\ mkey ->
382-
do
383-
key <- mkey
384-
pure
385-
([key]
386-
, pos
387-
, maybe
388-
(attrMissing (key :| mempty) Nothing)
389-
demand
390-
=<< maybe
391-
(withScopes scopes $ lookupVar key)
392-
(\ s ->
393-
do
394-
(coerce -> scope, _) <- fromValue @(AttrSet v, PositionSet) =<< s
395-
396-
clearScopes @v $ pushScope scope $ lookupVar key
397-
)
398-
ms
399-
)
400-
) <$>
401-
evalSetterKeyName nkeyname
375+
:: VarName
376+
-> ([VarName], SourcePos, m v)
377+
processScope var =
378+
([var]
379+
, pos
380+
, maybe
381+
(attrMissing (var :| mempty) Nothing)
382+
demand
383+
=<< maybe
384+
(withScopes scopes $ lookupVar var)
385+
(\ s ->
386+
do
387+
(coerce -> scope, _) <- fromValue @(AttrSet v, PositionSet) =<< s
388+
389+
clearScopes @v $ pushScope scope $ lookupVar var
390+
)
391+
ms
392+
)
402393

403394
moveOverridesLast = uncurry (<>) . partition
404395
(\case

src/Nix/Expr/Shorthands.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -267,7 +267,7 @@ mkSynHoleF = NSynHole . coerce
267267
-- | @inheritFrom x [a, b]@ | @inherit (x) a b;@ | @a = x.a;@ |
268268
-- | | | @b = x.b;@ |
269269
-- +------------------------+--------------------+------------+
270-
inheritFrom :: e -> [NKeyName e] -> Binding e
270+
inheritFrom :: e -> [VarName] -> Binding e
271271
inheritFrom expr ks = Inherit (pure expr) ks nullPos
272272

273273
-- | An `inherit` clause without an expression to pull from.
@@ -278,7 +278,7 @@ inheritFrom expr ks = Inherit (pure expr) ks nullPos
278278
-- | @inheritFrom [a, b]@ | @inherit a b;@ | @a = outside.a;@ |
279279
-- | | | @b = outside.b;@ |
280280
-- +----------------------+----------------+------------------+
281-
inherit :: [NKeyName e] -> Binding e
281+
inherit :: [VarName] -> Binding e
282282
inherit ks = Inherit Nothing ks nullPos
283283

284284
-- | Nix @=@ (bind operator).

src/Nix/Expr/Types.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -393,7 +393,7 @@ data Binding r
393393
-- ^ An explicit naming.
394394
--
395395
-- > NamedVar (StaticKey "x" :| [StaticKey "y"]) z SourcePos{} ~ x.y = z;
396-
| Inherit !(Maybe r) ![NKeyName r] !SourcePos
396+
| Inherit !(Maybe r) ![VarName] !SourcePos
397397
-- ^ Inheriting an attribute (binding) into the attribute set from the other scope (attribute set). No denoted scope means to inherit from the closest outside scope.
398398
--
399399
-- +---------------------------------------------------------------+--------------------+-----------------------+

src/Nix/Parser.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -450,7 +450,7 @@ nixBinders = (inherit <+> namedVar) `endBy` semi where
450450
p <- getSourcePos
451451
x <- whiteSpace *> optional scope
452452
liftA2 (Inherit x)
453-
(many keyName)
453+
(many identifier)
454454
(pure p)
455455
<?> "inherited binding"
456456
namedVar =

src/Nix/Pretty.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -164,7 +164,7 @@ prettyBind :: Binding (NixDoc ann) -> Doc ann
164164
prettyBind (NamedVar n v _p) =
165165
prettySelector n <> " = " <> withoutParens v <> ";"
166166
prettyBind (Inherit s ns _p) =
167-
"inherit " <> scope <> align (fillSep $ prettyKeyName <$> ns) <> ";"
167+
"inherit " <> scope <> align (fillSep $ prettyVarName <$> ns) <> ";"
168168
where
169169
scope =
170170
maybe

src/Nix/Reduce.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -453,7 +453,7 @@ pruneTree opts =
453453
pruneBinding (NamedVar xs (Just x) pos) = pure $ NamedVar (pruneKeyName <$> xs) x pos
454454
pruneBinding (Inherit _ [] _ ) = Nothing
455455
pruneBinding (Inherit (join -> Nothing) _ _ ) = Nothing
456-
pruneBinding (Inherit (join -> m) xs pos) = pure $ Inherit m (pruneKeyName <$> xs) pos
456+
pruneBinding (Inherit (join -> m) xs pos) = pure $ Inherit m xs pos
457457

458458
reducingEvalExpr
459459
:: (Framed e m, Has e Options, Exception r, MonadCatch m, MonadIO m)

src/Nix/TH.hs

Lines changed: 2 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -104,22 +104,18 @@ freeVars e = case unFix e of
104104
where
105105
bind1Def :: Binding r -> Set VarName
106106
bind1Def (Inherit Nothing _ _) = mempty
107-
bind1Def (Inherit (Just _ ) keys _) = Set.fromList $ mapMaybe staticKey keys
107+
bind1Def (Inherit (Just _ ) keys _) = Set.fromList keys
108108
bind1Def (NamedVar (StaticKey varname :| _) _ _) = one varname
109109
bind1Def (NamedVar (DynamicKey _ :| _) _ _) = mempty
110110

111111
bindFreeVars :: Foldable t => t (Binding NExpr) -> Set VarName
112112
bindFreeVars = foldMap bind1Free
113113
where
114114
bind1Free :: Binding NExpr -> Set VarName
115-
bind1Free (Inherit Nothing keys _) = Set.fromList $ mapMaybe staticKey keys
115+
bind1Free (Inherit Nothing keys _) = Set.fromList keys
116116
bind1Free (Inherit (Just scope) _ _) = freeVars scope
117117
bind1Free (NamedVar path expr _) = pathFree path <> freeVars expr
118118

119-
staticKey :: NKeyName r -> Maybe VarName
120-
staticKey (StaticKey varname) = pure varname
121-
staticKey (DynamicKey _ ) = Nothing
122-
123119
pathFree :: NAttrPath NExpr -> Set VarName
124120
pathFree = foldMap mapFreeVars
125121

tests/NixLanguageTests.hs

Lines changed: 10 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -66,12 +66,21 @@ newFailingTests = Set.fromList
6666
, "eval-okay-fromTOML"
6767
]
6868

69+
-- | Upstream tests that test cases that HNix disaded as a misfeature that is used so rarely
70+
-- that it more effective to fix it & lint it out of existance.
71+
deprecatedRareNixQuirkTests :: Set String
72+
deprecatedRareNixQuirkTests = Set.fromList
73+
[
74+
-- A rare quirk of Nix that is proper to fix&enforce then to support (see git commit history)
75+
"eval-okay-strings-as-attrs-names"
76+
]
77+
6978
genTests :: IO TestTree
7079
genTests = do
7180
testFiles <-
7281
sort
7382
-- Disabling the not yet done tests cases.
74-
. filter ((`Set.notMember` newFailingTests) . takeBaseName)
83+
. filter ((`Set.notMember` (newFailingTests `Set.union` deprecatedRareNixQuirkTests)) . takeBaseName)
7584
. filter ((/= ".xml") . takeExtension)
7685
<$> globDir1 (compile "*-*-*.*") "data/nix/tests/lang"
7786
let

tests/ParserTests.hs

Lines changed: 8 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -185,7 +185,7 @@ case_set_inherit =
185185
checks
186186
( mkNonRecSet
187187
[ "e" $= mkInt 3
188-
, inherit (StaticKey <$> ["a", "b"])
188+
, inherit ["a", "b"]
189189
]
190190
, "{ e = 3; inherit a b; }"
191191
)
@@ -197,7 +197,7 @@ case_set_scoped_inherit =
197197
checks
198198
( mkNonRecSet $
199199
(\ x -> [x, "e" $= mkInt 4, x]) $
200-
inheritFrom (var "a") (StaticKey <$> ["b", "c"])
200+
inheritFrom (var "a") ["b", "c"]
201201
, "{ inherit (a) b c; e = 4; inherit(a)b c; }"
202202
)
203203

@@ -207,15 +207,14 @@ case_set_inherit_direct =
207207
, "{ inherit ({a = 3;}); }"
208208
)
209209

210-
case_inherit_selector =
211-
checks
212-
( mkNonRecSet [inherit [DynamicKey (Plain (DoubleQuoted [Plain "a"]))]]
213-
, "{ inherit \"a\"; }"
214-
)
215-
216210
case_inherit_selector_syntax_mistakes =
217211
mistakes
218212
"{ inherit a.x; }"
213+
( -- A rare quirk of Nix that is proper to fix then to support (see git commit history)
214+
-- (old parser test result was):
215+
-- mkNonRecSet [inherit [DynamicKey (Plain (DoubleQuoted [Plain "a"]))]],
216+
"{ inherit \"a\"; }"
217+
)
219218

220219

221220
-- ** Lists
@@ -356,7 +355,7 @@ case_let_scoped_inherit =
356355
checks
357356
( mkLets
358357
[ "a" $= mkNull
359-
, inheritFrom (var "b") [StaticKey "c"]
358+
, inheritFrom (var "b") $ one "c"
360359
]
361360
$ var "c"
362361
, "let a = null; inherit (b) c; in c"

0 commit comments

Comments
 (0)