Refactor to not generate Parameters twice

This commit is contained in:
Vidar Holen 2022-07-27 19:47:37 -07:00
parent 3ce310e939
commit f440912279
4 changed files with 25 additions and 27 deletions

View File

@ -898,6 +898,10 @@ isClosingFileOp op =
T_IoDuplicate _ (T_LESSAND _) "-" -> True T_IoDuplicate _ (T_LESSAND _) "-" -> True
_ -> False _ -> False
getEnableDirectives root =
case root of
T_Annotation _ list _ -> [s | EnableComment s <- list]
_ -> []
return [] return []
runTests = $quickCheckAll runTests = $quickCheckAll

View File

@ -19,7 +19,7 @@
-} -}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleContexts #-}
module ShellCheck.Analytics (runAnalytics, optionalChecks, ShellCheck.Analytics.runTests) where module ShellCheck.Analytics (checker, optionalChecks, ShellCheck.Analytics.runTests) where
import ShellCheck.AST import ShellCheck.AST
import ShellCheck.ASTLib import ShellCheck.ASTLib
@ -71,29 +71,22 @@ treeChecks = [
,checkArrayValueUsedAsIndex ,checkArrayValueUsedAsIndex
] ]
runAnalytics :: AnalysisSpec -> [TokenComment] checker spec params = mkChecker spec params treeChecks
runAnalytics options =
runList options treeChecks ++ runList options optionalChecks mkChecker spec params checks =
Checker {
perScript = \(Root root) -> do
tell $ concatMap (\f -> f params root) all,
perToken = const $ return ()
}
where where
root = asScript options all = checks ++ optionals
optionals = getEnableDirectives root ++ asOptionalChecks options optionalKeys = asOptionalChecks spec
optionalChecks = optionals =
if "all" `elem` optionals if "all" `elem` optionalKeys
then map snd optionalTreeChecks then map snd optionalTreeChecks
else mapMaybe (\c -> Map.lookup c optionalCheckMap) optionals else mapMaybe (\c -> Map.lookup c optionalCheckMap) optionalKeys
runList :: AnalysisSpec -> [Parameters -> Token -> [TokenComment]]
-> [TokenComment]
runList spec list = notes
where
root = asScript spec
params = makeParameters spec
notes = concatMap (\f -> f params root) list
getEnableDirectives root =
case root of
T_Annotation _ list _ -> [s | EnableComment s <- list]
_ -> []
checkList l t = concatMap (\f -> f t) l checkList l t = concatMap (\f -> f t) l
@ -318,12 +311,12 @@ producesComments f s = not . null <$> runAndGetComments f s
runAndGetComments f s = do runAndGetComments f s = do
let pr = pScript s let pr = pScript s
prRoot pr root <- prRoot pr
let spec = defaultSpec pr let spec = defaultSpec pr
let params = makeParameters spec let params = makeParameters spec
return $ return $
filterByAnnotation spec params $ filterByAnnotation spec params $
runList spec [f] f params root
-- Copied from https://wiki.haskell.org/Edit_distance -- Copied from https://wiki.haskell.org/Edit_distance
dist :: Eq a => [a] -> [a] -> Int dist :: Eq a => [a] -> [a] -> Int

View File

@ -35,13 +35,13 @@ analyzeScript :: AnalysisSpec -> AnalysisResult
analyzeScript spec = newAnalysisResult { analyzeScript spec = newAnalysisResult {
arComments = arComments =
filterByAnnotation spec params . nub $ filterByAnnotation spec params . nub $
runAnalytics spec runChecker params (checkers spec params)
++ runChecker params (checkers spec params)
} }
where where
params = makeParameters spec params = makeParameters spec
checkers spec params = mconcat $ map ($ params) [ checkers spec params = mconcat $ map ($ params) [
ShellCheck.Analytics.checker spec,
ShellCheck.Checks.Commands.checker spec, ShellCheck.Checks.Commands.checker spec,
ShellCheck.Checks.ControlFlow.checker spec, ShellCheck.Checks.ControlFlow.checker spec,
ShellCheck.Checks.Custom.checker, ShellCheck.Checks.Custom.checker,

View File

@ -20,9 +20,10 @@
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
module ShellCheck.Checker (checkScript, ShellCheck.Checker.runTests) where module ShellCheck.Checker (checkScript, ShellCheck.Checker.runTests) where
import ShellCheck.Analyzer
import ShellCheck.ASTLib
import ShellCheck.Interface import ShellCheck.Interface
import ShellCheck.Parser import ShellCheck.Parser
import ShellCheck.Analyzer
import Data.Either import Data.Either
import Data.Functor import Data.Functor
@ -85,7 +86,7 @@ checkScript sys spec = do
asCheckSourced = csCheckSourced spec, asCheckSourced = csCheckSourced spec,
asExecutionMode = Executed, asExecutionMode = Executed,
asTokenPositions = tokenPositions, asTokenPositions = tokenPositions,
asOptionalChecks = csOptionalChecks spec asOptionalChecks = getEnableDirectives root ++ csOptionalChecks spec
} where as = newAnalysisSpec root } where as = newAnalysisSpec root
let analysisMessages = let analysisMessages =
maybe [] maybe []