Skip to content

Commit 85bef2c

Browse files
committed
Expr: Types: Annotated: pattern NBinary(_->AnnF)
1 parent 54c535e commit 85bef2c

File tree

4 files changed

+13
-13
lines changed

4 files changed

+13
-13
lines changed

src/Nix/Exec.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -268,7 +268,7 @@ instance MonadNix e t f m => MonadEval (NValue t f m) m where
268268
evalApp f x = do
269269
scope <- currentScopes
270270
span <- currentPos
271-
addProvenance (Provenance scope $ NBinary_ span NApp (pure f) Nothing) <$>
271+
addProvenance (Provenance scope $ NBinaryAnnF span NApp (pure f) Nothing) <$>
272272
(callFunc f =<< defer x)
273273

274274
evalAbs p k = do
@@ -376,7 +376,7 @@ execBinaryOp scope span op lval rarg =
376376
toBoolOp r b =
377377
pure $
378378
nvConstantP
379-
(Provenance scope $ NBinary_ span op (pure lval) r)
379+
(Provenance scope $ NBinaryAnnF span op (pure lval) r)
380380
(NBool b)
381381

382382
execBinaryOpForced
@@ -444,7 +444,7 @@ execBinaryOpForced scope span op lval rval = case op of
444444

445445
where
446446
prov :: Provenance m (NValue t f m)
447-
prov = Provenance scope $ NBinary_ span op (pure lval) (pure rval)
447+
prov = Provenance scope $ NBinaryAnnF span op (pure lval) (pure rval)
448448

449449
toBool = pure . nvConstantP prov . NBool
450450
compare :: (forall a. Ord a => a -> a -> Bool) -> m (NValue t f m)

src/Nix/Expr/Types/Annotated.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -219,8 +219,8 @@ pattern NEnvPathAnnF ann x = AnnF ann (NEnvPath x)
219219
pattern NUnaryAnnF :: SrcSpan -> NUnaryOp -> r -> NExprLocF r
220220
pattern NUnaryAnnF ann op x = AnnF ann (NUnary op x)
221221

222-
pattern NBinary_ :: SrcSpan -> NBinaryOp -> r -> r -> NExprLocF r
223-
pattern NBinary_ ann op x y = AnnF ann (NBinary op x y)
222+
pattern NBinaryAnnF :: SrcSpan -> NBinaryOp -> r -> r -> NExprLocF r
223+
pattern NBinaryAnnF ann op x y = AnnF ann (NBinary op x y)
224224

225225
pattern NSelect_ :: SrcSpan -> Maybe r -> r -> NAttrPath r -> NExprLocF r
226226
pattern NSelect_ ann v x p = AnnF ann (NSelect v x p)
@@ -245,7 +245,7 @@ pattern NAssert_ ann x y = AnnF ann (NAssert x y)
245245

246246
pattern NSynHole_ :: SrcSpan -> VarName -> NExprLocF r
247247
pattern NSynHole_ ann x = AnnF ann (NSynHole x)
248-
{-# complete NConstantAnnF, NStrAnnF, NSymAnnF, NListAnnF, NSetAnnF, NLiteralPathAnnF, NEnvPathAnnF, NUnaryAnnF, NBinary_, NSelect_, NHasAttr_, NAbs_, NLet_, NIf_, NWith_, NAssert_, NSynHole_ #-}
248+
{-# complete NConstantAnnF, NStrAnnF, NSymAnnF, NListAnnF, NSetAnnF, NLiteralPathAnnF, NEnvPathAnnF, NUnaryAnnF, NBinaryAnnF, NSelect_, NHasAttr_, NAbs_, NLet_, NIf_, NWith_, NAssert_, NSynHole_ #-}
249249

250250

251251
pattern PNConstant :: SrcSpan -> NAtom -> NExprLoc

src/Nix/Reduce.hs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -170,12 +170,12 @@ reduce (NUnaryAnnF uann op arg) =
170170
--
171171
-- * Reduce a lambda function by adding its name to the local
172172
-- scope and recursively reducing its body.
173-
reduce (NBinary_ bann NApp fun arg) = fun >>= \case
173+
reduce (NBinaryAnnF bann NApp fun arg) = fun >>= \case
174174
f@(Fix (NSymAnnF _ "import")) ->
175175
(\case
176176
-- Fix (NEnvPathAnnF pann origPath) -> staticImport pann origPath
177177
Fix (NLiteralPathAnnF pann origPath) -> staticImport pann origPath
178-
v -> pure $ Fix $ NBinary_ bann NApp f v
178+
v -> pure $ Fix $ NBinaryAnnF bann NApp f v
179179
) =<< arg
180180

181181
Fix (NAbs_ _ (Param name) body) ->
@@ -185,17 +185,17 @@ reduce (NBinary_ bann NApp fun arg) = fun >>= \case
185185
(coerce $ HM.singleton name x)
186186
(foldFix reduce body)
187187

188-
f -> Fix . NBinary_ bann NApp f <$> arg
188+
f -> Fix . NBinaryAnnF bann NApp f <$> arg
189189

190190
-- | Reduce an integer addition to its result.
191-
reduce (NBinary_ bann op larg rarg) =
191+
reduce (NBinaryAnnF bann op larg rarg) =
192192
do
193193
lval <- larg
194194
rval <- rarg
195195
pure $ Fix $
196196
case (op, lval, rval) of
197197
(NPlus, Fix (NConstantAnnF ann (NInt x)), Fix (NConstantAnnF _ (NInt y))) -> NConstantAnnF ann $ NInt $ x + y
198-
_ -> NBinary_ bann op lval rval
198+
_ -> NBinaryAnnF bann op lval rval
199199

200200
-- | Reduce a select on a Set by substituting the set to the selected value.
201201
--

tests/ParserTests.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -651,11 +651,11 @@ case_simpleLoc =
651651
[ NamedVar
652652
(StaticKey "foo" :| [])
653653
(Fix
654-
(NBinary_
654+
(NBinaryAnnF
655655
(mkSpan 2 7 3 15)
656656
NApp
657657
(Fix
658-
(NBinary_
658+
(NBinaryAnnF
659659
(mkSpan 2 7 3 9)
660660
NApp
661661
(Fix (NSymAnnF (mkSpan 2 7 2 10) "bar"))

0 commit comments

Comments
 (0)