Skip to content

Commit 46a82e3

Browse files
committed
treewide: use pattern AnnE, add doc to it
1 parent ef2700b commit 46a82e3

File tree

5 files changed

+20
-22
lines changed

5 files changed

+20
-22
lines changed

src/Nix/Cited/Basic.hs

Lines changed: 6 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -16,7 +16,6 @@ import Prelude hiding ( force )
1616
import Control.Comonad ( Comonad )
1717
import Control.Comonad.Env ( ComonadEnv )
1818
import Control.Monad.Catch hiding ( catchJust )
19-
import Data.Fix
2019
import Nix.Cited
2120
import Nix.Eval as Eval
2221
import Nix.Exec
@@ -64,13 +63,12 @@ instance ( Has e Options
6463

6564
-- Gather the current evaluation context at the time of thunk
6665
-- creation, and record it along with the thunk.
67-
let go (fromException ->
68-
Just (EvaluatingExpr scope
69-
(Fix (Compose (Ann s e))))) =
70-
let e' = Compose (Ann s (Nothing <$ e))
71-
in [Provenance scope e']
72-
go _ = mempty
73-
ps = concatMap (go . frame) frames
66+
let
67+
go (fromException -> Just (EvaluatingExpr scope (AnnE s e))) =
68+
let e' = Compose (Ann s (Nothing <$ e)) in
69+
[Provenance scope e']
70+
go _ = mempty
71+
ps = concatMap (go . frame) frames
7472

7573
Cited . NCited ps <$> thunk mv
7674
)

src/Nix/Eval.hs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -15,7 +15,6 @@ module Nix.Eval where
1515
import Control.Monad ( foldM )
1616
import Control.Monad.Fix ( MonadFix )
1717
import Data.Semialign.Indexed ( ialignWith )
18-
import Data.Fix ( Fix(Fix) )
1918
import qualified Data.HashMap.Lazy as M
2019
import Data.List ( partition )
2120
import Data.These ( These(..) )
@@ -496,7 +495,7 @@ buildArgument params arg =
496495

497496
addSourcePositions
498497
:: (MonadReader e m, Has e SrcSpan) => Transform NExprLocF (m a)
499-
addSourcePositions f v@(Fix (Compose (Ann ann _))) =
498+
addSourcePositions f v@(AnnE ann _) =
500499
local (set hasLens ann) $ f v
501500

502501
addStackFrames

src/Nix/Expr/Types/Annotated.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -84,6 +84,7 @@ data Ann ann a = Ann
8484

8585
type AnnF ann f = Compose (Ann ann) f
8686

87+
-- | Pattern: @Fix (Compose (Ann _ _))@.
8788
pattern AnnE
8889
:: forall ann (g :: * -> *)
8990
. ann

src/Nix/Reduce.hs

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -373,7 +373,7 @@ pruneTree opts =
373373
(reduceSets opts) -- Reduce set members that aren't used; breaks if hasAttr is used
374374
binds
375375

376-
NLet binds (Just body@(Fix (Compose (Ann _ x)))) ->
376+
NLet binds (Just body@(AnnE _ x)) ->
377377
pure $
378378
list
379379
x
@@ -384,8 +384,8 @@ pruneTree opts =
384384
pure $ NSelect aset (NE.map pruneKeyName attr) (join alt)
385385

386386
-- These are the only short-circuiting binary operators
387-
NBinary NAnd (Just (Fix (Compose (Ann _ larg)))) _ -> pure larg
388-
NBinary NOr (Just (Fix (Compose (Ann _ larg)))) _ -> pure larg
387+
NBinary NAnd (Just (AnnE _ larg)) _ -> pure larg
388+
NBinary NOr (Just (AnnE _ larg)) _ -> pure larg
389389

390390
-- If the function was never called, it means its argument was in a
391391
-- thunk that was forced elsewhere.
@@ -399,18 +399,18 @@ pruneTree opts =
399399
NBinary op (Just larg) Nothing -> pure $ NBinary op larg nNull
400400

401401
-- If the scope of a with was never referenced, it's not needed
402-
NWith Nothing (Just (Fix (Compose (Ann _ body)))) -> pure body
402+
NWith Nothing (Just (AnnE _ body)) -> pure body
403403

404404
NAssert Nothing _ ->
405405
fail "How can an assert be used, but its condition not?"
406406

407-
NAssert _ (Just (Fix (Compose (Ann _ body)))) -> pure body
407+
NAssert _ (Just (AnnE _ body)) -> pure body
408408
NAssert (Just cond) _ -> pure $ NAssert cond nNull
409409

410410
NIf Nothing _ _ -> fail "How can an if be used, but its condition not?"
411411

412-
NIf _ Nothing (Just (Fix (Compose (Ann _ f)))) -> pure f
413-
NIf _ (Just (Fix (Compose (Ann _ t)))) Nothing -> pure t
412+
NIf _ Nothing (Just (AnnE _ f)) -> pure f
413+
NIf _ (Just (AnnE _ t)) Nothing -> pure t
414414

415415
x -> sequence x
416416

src/Nix/Render/Frame.hs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -72,7 +72,7 @@ framePos
7272
-> Maybe SourcePos
7373
framePos (NixFrame _ f)
7474
| Just (e :: EvalFrame m v) <- fromException f = case e of
75-
EvaluatingExpr _ (Fix (Compose (Ann (SrcSpan beg _) _))) -> pure beg
75+
EvaluatingExpr _ (AnnE (SrcSpan beg _) _) -> pure beg
7676
_ -> Nothing
7777
| otherwise = Nothing
7878

@@ -108,7 +108,7 @@ renderEvalFrame level f =
108108
do
109109
opts :: Options <- asks (view hasLens)
110110
case f of
111-
EvaluatingExpr scope e@(Fix (Compose (Ann ann _))) ->
111+
EvaluatingExpr scope e@(AnnE ann _) ->
112112
do
113113
let
114114
scopeInfo =
@@ -121,7 +121,7 @@ renderEvalFrame level f =
121121
$ renderLocation ann =<<
122122
renderExpr level "While evaluating" "Expression" e
123123

124-
ForcingExpr _scope e@(Fix (Compose (Ann ann _))) | thunks opts ->
124+
ForcingExpr _scope e@(AnnE ann _) | thunks opts ->
125125
fmap
126126
(: mempty)
127127
$ renderLocation ann =<<
@@ -135,7 +135,7 @@ renderEvalFrame level f =
135135

136136
SynHole synfo ->
137137
sequence $
138-
let e@(Fix (Compose (Ann ann _))) = _synHoleInfo_expr synfo in
138+
let e@(AnnE ann _) = _synHoleInfo_expr synfo in
139139

140140
[ renderLocation ann =<<
141141
renderExpr level "While evaluating" "Syntactic Hole" e
@@ -152,7 +152,7 @@ renderExpr
152152
-> Text
153153
-> NExprLoc
154154
-> m (Doc ann)
155-
renderExpr _level longLabel shortLabel e@(Fix (Compose (Ann _ x))) = do
155+
renderExpr _level longLabel shortLabel e@(AnnE _ x) = do
156156
opts :: Options <- asks (view hasLens)
157157
let rendered
158158
| verbose opts >= DebugInfo =

0 commit comments

Comments
 (0)