Skip to content

Commit

Permalink
UnusedLetBind: speed up
Browse files Browse the repository at this point in the history
We only need to check each piece of code for free variables once
  • Loading branch information
Radvendii committed Nov 14, 2021
1 parent e51dbac commit 69a193d
Show file tree
Hide file tree
Showing 2 changed files with 58 additions and 9 deletions.
26 changes: 18 additions & 8 deletions src/Nix/Linter/Checks.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,8 +25,9 @@ import Nix.Expr.Types
import Nix.Expr.Types.Annotated

import Nix.Linter.Tools
import Nix.Linter.Tools.FreeVars
import Nix.Linter.Types
import Nix.Linter.Utils (choose, sorted, (<$$>), (<&>))
import Nix.Linter.Utils (choose, sorted, (<$$>))

varName :: Text
varName = "varName"
Expand All @@ -35,15 +36,16 @@ checkUnusedLetBinding :: CheckBase
checkUnusedLetBinding warn e = [ (warn UnusedLetBind)
& setLoc loc
& note' varName name
| NLet_ srcSpan binds usedIn <- [unFix e]
, (bind, others) <- choose binds
| NLet_ _ binds _ <- [unFix e]
, free <- [freeVarsIgnoreTopBinds' e]
, bind <- binds
, (name, loc) <- case bind of
NamedVar (StaticKey name :| []) _ loc -> [(name, loc)]
Inherit _ keys loc -> do
StaticKey name <- keys
[(name, loc)]
_ -> []
, noRef name $ Fix $ NLet_ srcSpan others usedIn
, not $ Set.member name free
]

checkUnusedArg :: CheckBase
Expand All @@ -70,10 +72,18 @@ checkEmptyInherit warn e = [ (warn EmptyInherit) {pos=singletonSpan loc}
checkUnneededRec :: CheckBase
checkUnneededRec warn e = [ warn UnneededRec
| NSet_ _ann NRecursive binds <- [unFix e]
, not $ or $ choose binds <&> \case
(bind, others) -> case bind of
NamedVar (StaticKey name :| []) _ _ -> all (noRef name) (values others)
_ -> False
, not . or $ do
(bind, others) <- choose binds
name <- case bind of
NamedVar (StaticKey name :| []) _ _ -> [name]
Inherit _ keys _ -> do
StaticKey name <- keys
[name]
-- References to dynamic keys are not allowed
-- e.g. rec { x = "hi"; ${x} = 5; y = hi; }
-- will fail to evaluate, so we don't need to account for it
_ -> []
pure $ hasRef name $ Fix $ NSet_ _ann NRecursive others
]

checkOpBase :: OffenseCategory -> Pair (UnwrappedNExprLoc -> Bool) -> NBinaryOp -> Bool -> CheckBase
Expand Down
41 changes: 40 additions & 1 deletion src/Nix/Linter/Tools/FreeVars.hs
Original file line number Diff line number Diff line change
@@ -1,9 +1,48 @@
module Nix.Linter.Tools.FreeVars (freeVars, freeVars') where
module Nix.Linter.Tools.FreeVars (freeVars, freeVars', freeVarsIgnoreTopBinds
, freeVarsIgnoreTopBinds') where
import Data.Set (Set)

import Nix.Expr.Types
import Nix.Expr.Types.Annotated
import Nix.TH (freeVars)

import qualified Data.Set as Set
import Data.Maybe (mapMaybe)
import Data.Fix (unFix, Fix (..))

freeVars' :: NExprLoc -> Set VarName
freeVars' = freeVars . stripAnnotation

freeVarsIgnoreTopBinds' :: NExprLoc -> Set VarName
freeVarsIgnoreTopBinds' = freeVarsIgnoreTopBinds . stripAnnotation

-- gets the free variables of the expression, assuming the top level bindings
-- were not bound. Note that this function is *not* recursive, since we want to
-- count bindings deeper in the tree
freeVarsIgnoreTopBinds :: NExpr -> Set VarName
freeVarsIgnoreTopBinds e =
case unFix e of
(NSet NRecursive bindings) -> bindFreeVars bindings
(NAbs (Param _) expr) -> freeVars expr
(NAbs (ParamSet set _ _) expr) ->
freeVars expr <> (Set.unions $ freeVars <$> mapMaybe snd set)
(NLet bindings expr) -> freeVars expr <> bindFreeVars bindings
noTopBinds -> freeVars $ Fix noTopBinds
where
bindFreeVars :: Foldable t => t (Binding NExpr) -> Set VarName
bindFreeVars = foldMap bind1Free
where
bind1Free :: Binding NExpr -> Set VarName
bind1Free (Inherit Nothing keys _) = Set.fromList $ mapMaybe staticKey keys
bind1Free (Inherit (Just scope) _ _) = freeVars scope
bind1Free (NamedVar path expr _) = pathFree path <> freeVars expr

staticKey :: NKeyName r -> Maybe VarName
staticKey (StaticKey varname) = pure varname
staticKey (DynamicKey _ ) = mempty

pathFree :: NAttrPath NExpr -> Set VarName
pathFree = foldMap mapFreeVars

mapFreeVars :: Foldable t => t NExpr -> Set VarName
mapFreeVars = foldMap freeVars

0 comments on commit 69a193d

Please sign in to comment.