mirror of
https://github.com/koalaman/shellcheck
synced 2025-07-16 10:03:08 -07:00
Add extended-analysis directive to toggle DFA
This commit is contained in:
parent
1565091b1d
commit
d80fdfa9e8
12 changed files with 128 additions and 22 deletions
|
@ -152,6 +152,7 @@ data Annotation =
|
|||
| ShellOverride String
|
||||
| SourcePath String
|
||||
| ExternalSources Bool
|
||||
| ExtendedAnalysis Bool
|
||||
deriving (Show, Eq)
|
||||
data ConditionType = DoubleBracket | SingleBracket deriving (Show, Eq)
|
||||
|
||||
|
|
|
@ -910,5 +910,11 @@ getEnableDirectives root =
|
|||
T_Annotation _ list _ -> [s | EnableComment s <- list]
|
||||
_ -> []
|
||||
|
||||
getExtendedAnalysisDirective :: Token -> Maybe Bool
|
||||
getExtendedAnalysisDirective root =
|
||||
case root of
|
||||
T_Annotation _ list _ -> listToMaybe $ [s | ExtendedAnalysis s <- list]
|
||||
_ -> Nothing
|
||||
|
||||
return []
|
||||
runTests = $quickCheckAll
|
||||
|
|
|
@ -1262,7 +1262,8 @@ checkNumberComparisons params (TC_Binary id typ op lhs rhs) = do
|
|||
str = concat $ oversimplify c
|
||||
var = getBracedReference str
|
||||
in fromMaybe False $ do
|
||||
state <- CF.getIncomingState (cfgAnalysis params) id
|
||||
cfga <- cfgAnalysis params
|
||||
state <- CF.getIncomingState cfga id
|
||||
value <- Map.lookup var $ CF.variablesInScope state
|
||||
return $ CF.numericalStatus (CF.variableValue value) >= CF.NumericalStatusMaybe
|
||||
_ ->
|
||||
|
@ -2143,7 +2144,8 @@ checkSpacefulnessCfg' dirtyPass params token@(T_DollarBraced id _ list) =
|
|||
&& not (usedAsCommandName parents token)
|
||||
|
||||
isClean = fromMaybe False $ do
|
||||
state <- CF.getIncomingState (cfgAnalysis params) id
|
||||
cfga <- cfgAnalysis params
|
||||
state <- CF.getIncomingState cfga id
|
||||
value <- Map.lookup name $ CF.variablesInScope state
|
||||
return $ isCleanState value
|
||||
|
||||
|
@ -4896,7 +4898,8 @@ prop_checkCommandIsUnreachable3 = verifyNot checkCommandIsUnreachable "foo; bar
|
|||
checkCommandIsUnreachable params t =
|
||||
case t of
|
||||
T_Pipeline {} -> sequence_ $ do
|
||||
state <- CF.getIncomingState (cfgAnalysis params) id
|
||||
cfga <- cfgAnalysis params
|
||||
state <- CF.getIncomingState cfga id
|
||||
guard . not $ CF.stateIsReachable state
|
||||
guard . not $ isSourced params t
|
||||
return $ info id 2317 "Command appears to be unreachable. Check usage (or ignore if invoked indirectly)."
|
||||
|
@ -4918,14 +4921,15 @@ checkOverwrittenExitCode params t =
|
|||
_ -> return ()
|
||||
where
|
||||
check id = sequence_ $ do
|
||||
state <- CF.getIncomingState (cfgAnalysis params) id
|
||||
cfga <- cfgAnalysis params
|
||||
state <- CF.getIncomingState cfga id
|
||||
let exitCodeIds = CF.exitCodes state
|
||||
guard . not $ S.null exitCodeIds
|
||||
|
||||
let idToToken = idMap params
|
||||
exitCodeTokens <- traverse (\k -> Map.lookup k idToToken) $ S.toList exitCodeIds
|
||||
return $ do
|
||||
when (all isCondition exitCodeTokens && not (usedUnconditionally t exitCodeIds)) $
|
||||
when (all isCondition exitCodeTokens && not (usedUnconditionally cfga t exitCodeIds)) $
|
||||
warn id 2319 "This $? refers to a condition, not a command. Assign to a variable to avoid it being overwritten."
|
||||
when (all isPrinting exitCodeTokens) $
|
||||
warn id 2320 "This $? refers to echo/printf, not a previous command. Assign to variable to avoid it being overwritten."
|
||||
|
@ -4938,8 +4942,8 @@ checkOverwrittenExitCode params t =
|
|||
|
||||
-- If we don't do anything based on the condition, assume we wanted the condition itself
|
||||
-- This helps differentiate `x; [ $? -gt 0 ] && exit $?` vs `[ cond ]; exit $?`
|
||||
usedUnconditionally t testIds =
|
||||
all (\c -> CF.doesPostDominate (cfgAnalysis params) (getId t) c) testIds
|
||||
usedUnconditionally cfga t testIds =
|
||||
all (\c -> CF.doesPostDominate cfga (getId t) c) testIds
|
||||
|
||||
isPrinting t =
|
||||
case getCommandBasename t of
|
||||
|
@ -5009,7 +5013,8 @@ prop_checkPlusEqualsNumber9 = verifyNot checkPlusEqualsNumber "declare -ia var;
|
|||
checkPlusEqualsNumber params t =
|
||||
case t of
|
||||
T_Assignment id Append var _ word -> sequence_ $ do
|
||||
state <- CF.getIncomingState (cfgAnalysis params) id
|
||||
cfga <- cfgAnalysis params
|
||||
state <- CF.getIncomingState cfga id
|
||||
guard $ isNumber state word
|
||||
guard . not $ fromMaybe False $ CF.variableMayBeDeclaredInteger state var
|
||||
return $ warn id 2324 "var+=1 will append, not increment. Use (( var += 1 )), declare -i var, or quote number to silence."
|
||||
|
|
|
@ -104,7 +104,7 @@ data Parameters = Parameters {
|
|||
-- map from token id to start and end position
|
||||
tokenPositions :: Map.Map Id (Position, Position),
|
||||
-- Result from Control Flow Graph analysis (including data flow analysis)
|
||||
cfgAnalysis :: CF.CFGAnalysis
|
||||
cfgAnalysis :: Maybe CF.CFGAnalysis
|
||||
} deriving (Show)
|
||||
|
||||
-- TODO: Cache results of common AST ops here
|
||||
|
@ -197,8 +197,10 @@ makeCommentWithFix severity id code str fix =
|
|||
}
|
||||
in force withFix
|
||||
|
||||
-- makeParameters :: CheckSpec -> Parameters
|
||||
makeParameters spec = params
|
||||
where
|
||||
extendedAnalysis = fromMaybe True $ msum [asExtendedAnalysis spec, getExtendedAnalysisDirective root]
|
||||
params = Parameters {
|
||||
rootNode = root,
|
||||
shellType = fromMaybe (determineShell (asFallbackShell spec) root) $ asShellType spec,
|
||||
|
@ -229,7 +231,9 @@ makeParameters spec = params
|
|||
parentMap = getParentTree root,
|
||||
variableFlow = getVariableFlow params root,
|
||||
tokenPositions = asTokenPositions spec,
|
||||
cfgAnalysis = CF.analyzeControlFlow cfParams root
|
||||
cfgAnalysis = do
|
||||
guard extendedAnalysis
|
||||
return $ CF.analyzeControlFlow cfParams root
|
||||
}
|
||||
cfParams = CF.CFGParameters {
|
||||
CF.cfLastpipe = hasLastpipe params,
|
||||
|
|
|
@ -25,6 +25,7 @@ import ShellCheck.ASTLib
|
|||
import ShellCheck.Interface
|
||||
import ShellCheck.Parser
|
||||
|
||||
import Debug.Trace -- DO NOT SUBMIT
|
||||
import Data.Either
|
||||
import Data.Functor
|
||||
import Data.List
|
||||
|
@ -86,6 +87,7 @@ checkScript sys spec = do
|
|||
asCheckSourced = csCheckSourced spec,
|
||||
asExecutionMode = Executed,
|
||||
asTokenPositions = tokenPositions,
|
||||
asExtendedAnalysis = csExtendedAnalysis spec,
|
||||
asOptionalChecks = getEnableDirectives root ++ csOptionalChecks spec
|
||||
} where as = newAnalysisSpec root
|
||||
let analysisMessages =
|
||||
|
@ -520,5 +522,43 @@ prop_hereDocsWillHaveParsedIndices = null result
|
|||
where
|
||||
result = check "#!/bin/bash\nmy_array=(a b)\ncat <<EOF >> ./test\n $(( 1 + my_array[1] ))\nEOF"
|
||||
|
||||
prop_rcCanSuppressDfa = null result
|
||||
where
|
||||
result = checkWithRc "extended-analysis=false" emptyCheckSpec {
|
||||
csScript = "#!/bin/sh\nexit; foo;"
|
||||
}
|
||||
|
||||
prop_fileCanSuppressDfa = null $ traceShowId result
|
||||
where
|
||||
result = checkWithRc "" emptyCheckSpec {
|
||||
csScript = "#!/bin/sh\n# shellcheck extended-analysis=false\nexit; foo;"
|
||||
}
|
||||
|
||||
prop_fileWinsWhenSuppressingDfa1 = null result
|
||||
where
|
||||
result = checkWithRc "extended-analysis=true" emptyCheckSpec {
|
||||
csScript = "#!/bin/sh\n# shellcheck extended-analysis=false\nexit; foo;"
|
||||
}
|
||||
|
||||
prop_fileWinsWhenSuppressingDfa2 = result == [2317]
|
||||
where
|
||||
result = checkWithRc "extended-analysis=false" emptyCheckSpec {
|
||||
csScript = "#!/bin/sh\n# shellcheck extended-analysis=true\nexit; foo;"
|
||||
}
|
||||
|
||||
prop_flagWinsWhenSuppressingDfa1 = result == [2317]
|
||||
where
|
||||
result = checkWithRc "extended-analysis=false" emptyCheckSpec {
|
||||
csScript = "#!/bin/sh\n# shellcheck extended-analysis=false\nexit; foo;",
|
||||
csExtendedAnalysis = Just True
|
||||
}
|
||||
|
||||
prop_flagWinsWhenSuppressingDfa2 = null result
|
||||
where
|
||||
result = checkWithRc "extended-analysis=true" emptyCheckSpec {
|
||||
csScript = "#!/bin/sh\n# shellcheck extended-analysis=true\nexit; foo;",
|
||||
csExtendedAnalysis = Just False
|
||||
}
|
||||
|
||||
return []
|
||||
runTests = $quickCheckAll
|
||||
|
|
|
@ -1430,26 +1430,28 @@ prop_checkBackreferencingDeclaration6 = verify (checkBackreferencingDeclaration
|
|||
prop_checkBackreferencingDeclaration7 = verify (checkBackreferencingDeclaration "declare") "declare x=var $k=$x"
|
||||
checkBackreferencingDeclaration cmd = CommandCheck (Exactly cmd) check
|
||||
where
|
||||
check t = foldM_ perArg M.empty $ arguments t
|
||||
check t = do
|
||||
cfga <- asks cfgAnalysis
|
||||
when (isJust cfga) $
|
||||
foldM_ (perArg $ fromJust cfga) M.empty $ arguments t
|
||||
|
||||
perArg leftArgs t =
|
||||
perArg cfga leftArgs t =
|
||||
case t of
|
||||
T_Assignment id _ name idx t -> do
|
||||
warnIfBackreferencing leftArgs $ t:idx
|
||||
warnIfBackreferencing cfga leftArgs $ t:idx
|
||||
return $ M.insert name id leftArgs
|
||||
t -> do
|
||||
warnIfBackreferencing leftArgs [t]
|
||||
warnIfBackreferencing cfga leftArgs [t]
|
||||
return leftArgs
|
||||
|
||||
warnIfBackreferencing backrefs l = do
|
||||
references <- findReferences l
|
||||
warnIfBackreferencing cfga backrefs l = do
|
||||
references <- findReferences cfga l
|
||||
let reused = M.intersection backrefs references
|
||||
mapM msg $ M.toList reused
|
||||
|
||||
msg (name, id) = warn id 2318 $ "This assignment is used again in this '" ++ cmd ++ "', but won't have taken effect. Use two '" ++ cmd ++ "'s."
|
||||
|
||||
findReferences list = do
|
||||
cfga <- asks cfgAnalysis
|
||||
findReferences cfga list = do
|
||||
let graph = CF.graph cfga
|
||||
let nodesMap = CF.tokenToNodes cfga
|
||||
let nodes = S.unions $ map (\id -> M.findWithDefault S.empty id nodesMap) $ map getId $ list
|
||||
|
|
|
@ -78,7 +78,7 @@ controlFlowEffectChecks = [
|
|||
runNodeChecks :: [ControlFlowNodeCheck] -> ControlFlowCheck
|
||||
runNodeChecks perNode = do
|
||||
cfg <- asks cfgAnalysis
|
||||
runOnAll cfg
|
||||
sequence_ $ runOnAll <$> cfg
|
||||
where
|
||||
getData datas n@(node, label) = do
|
||||
(pre, post) <- M.lookup node datas
|
||||
|
|
|
@ -21,11 +21,11 @@
|
|||
module ShellCheck.Interface
|
||||
(
|
||||
SystemInterface(..)
|
||||
, CheckSpec(csFilename, csScript, csCheckSourced, csIncludedWarnings, csExcludedWarnings, csShellTypeOverride, csMinSeverity, csIgnoreRC, csOptionalChecks)
|
||||
, CheckSpec(csFilename, csScript, csCheckSourced, csIncludedWarnings, csExcludedWarnings, csShellTypeOverride, csMinSeverity, csIgnoreRC, csExtendedAnalysis, csOptionalChecks)
|
||||
, CheckResult(crFilename, crComments)
|
||||
, ParseSpec(psFilename, psScript, psCheckSourced, psIgnoreRC, psShellTypeOverride)
|
||||
, ParseResult(prComments, prTokenPositions, prRoot)
|
||||
, AnalysisSpec(asScript, asShellType, asFallbackShell, asExecutionMode, asCheckSourced, asTokenPositions, asOptionalChecks)
|
||||
, AnalysisSpec(asScript, asShellType, asFallbackShell, asExecutionMode, asCheckSourced, asTokenPositions, asExtendedAnalysis, asOptionalChecks)
|
||||
, AnalysisResult(arComments)
|
||||
, FormatterOptions(foColorOption, foWikiLinkCount)
|
||||
, Shell(Ksh, Sh, Bash, Dash, BusyboxSh)
|
||||
|
@ -100,6 +100,7 @@ data CheckSpec = CheckSpec {
|
|||
csIncludedWarnings :: Maybe [Integer],
|
||||
csShellTypeOverride :: Maybe Shell,
|
||||
csMinSeverity :: Severity,
|
||||
csExtendedAnalysis :: Maybe Bool,
|
||||
csOptionalChecks :: [String]
|
||||
} deriving (Show, Eq)
|
||||
|
||||
|
@ -124,6 +125,7 @@ emptyCheckSpec = CheckSpec {
|
|||
csIncludedWarnings = Nothing,
|
||||
csShellTypeOverride = Nothing,
|
||||
csMinSeverity = StyleC,
|
||||
csExtendedAnalysis = Nothing,
|
||||
csOptionalChecks = []
|
||||
}
|
||||
|
||||
|
@ -174,6 +176,7 @@ data AnalysisSpec = AnalysisSpec {
|
|||
asExecutionMode :: ExecutionMode,
|
||||
asCheckSourced :: Bool,
|
||||
asOptionalChecks :: [String],
|
||||
asExtendedAnalysis :: Maybe Bool,
|
||||
asTokenPositions :: Map.Map Id (Position, Position)
|
||||
}
|
||||
|
||||
|
@ -184,6 +187,7 @@ newAnalysisSpec token = AnalysisSpec {
|
|||
asExecutionMode = Executed,
|
||||
asCheckSourced = False,
|
||||
asOptionalChecks = [],
|
||||
asExtendedAnalysis = Nothing,
|
||||
asTokenPositions = Map.empty
|
||||
}
|
||||
|
||||
|
|
|
@ -1058,6 +1058,16 @@ readAnnotationWithoutPrefix sandboxed = do
|
|||
"This shell type is unknown. Use e.g. sh or bash."
|
||||
return [ShellOverride shell]
|
||||
|
||||
"extended-analysis" -> do
|
||||
pos <- getPosition
|
||||
value <- plainOrQuoted $ many1 letter
|
||||
case value of
|
||||
"true" -> return [ExtendedAnalysis True]
|
||||
"false" -> return [ExtendedAnalysis False]
|
||||
_ -> do
|
||||
parseNoteAt pos ErrorC 1146 "Unknown extended-analysis value. Expected true/false."
|
||||
return []
|
||||
|
||||
"external-sources" -> do
|
||||
pos <- getPosition
|
||||
value <- plainOrQuoted $ many1 letter
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue