Warn when $? refers to echo or condition (ref #2541)

This commit is contained in:
Vidar Holen 2022-07-23 09:38:58 -07:00
parent b261ec24f9
commit 5cf6e01ce9
4 changed files with 42 additions and 0 deletions

View File

@ -3,6 +3,7 @@
- SC2316: Warn about 'local readonly foo' and similar (thanks, patrickxia!) - SC2316: Warn about 'local readonly foo' and similar (thanks, patrickxia!)
- SC2317: Warn about unreachable commands - SC2317: Warn about unreachable commands
- SC2318: Warn about backreferences in 'declare x=1 y=$x' - SC2318: Warn about backreferences in 'declare x=1 y=$x'
- SC2319/SC2320: Warn when $? refers to echo/printf/[ ]/[[ ]]/test
### Fixed ### Fixed
- SC2086: Now uses DFA to make more accurate predictions about values - SC2086: Now uses DFA to make more accurate predictions about values

View File

@ -205,6 +205,7 @@ nodeChecks = [
,checkBatsTestDoesNotUseNegation ,checkBatsTestDoesNotUseNegation
,checkCommandIsUnreachable ,checkCommandIsUnreachable
,checkSpacefulnessCfg ,checkSpacefulnessCfg
,checkOverwrittenExitCode
] ]
optionalChecks = map fst optionalTreeChecks optionalChecks = map fst optionalTreeChecks
@ -4876,5 +4877,41 @@ checkCommandIsUnreachable params t =
_ -> return () _ -> return ()
where id = getId t where id = getId t
prop_checkOverwrittenExitCode1 = verify checkOverwrittenExitCode "x; [ $? -eq 1 ] || [ $? -eq 2 ]"
prop_checkOverwrittenExitCode2 = verifyNot checkOverwrittenExitCode "x; [ $? -eq 1 ]"
prop_checkOverwrittenExitCode3 = verify checkOverwrittenExitCode "x; echo \"Exit is $?\"; [ $? -eq 0 ]"
prop_checkOverwrittenExitCode4 = verifyNot checkOverwrittenExitCode "x; [ $? -eq 0 ]"
checkOverwrittenExitCode params t =
case t of
T_DollarBraced id _ val | getLiteralString val == Just "?" -> check id
_ -> return ()
where
check id = sequence_ $ do
state <- CF.getIncomingState (cfgAnalysis params) id
let exitCodeIds = CF.exitCodes state
guard . not $ S.null exitCodeIds
let idToToken = idMap params
exitCodeTokens <- sequence $ map (\k -> Map.lookup k idToToken) $ S.toList exitCodeIds
return $ do
when (all isCondition exitCodeTokens) $
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."
isCondition t =
case t of
T_Condition {} -> True
T_SimpleCommand {} -> getCommandName t == Just "test"
_ -> False
isPrinting t =
case getCommandBasename t of
Just "echo" -> True
Just "printf" -> True
_ -> False
return [] return []
runTests = $( [| $(forAllProperties) (quickCheckWithResult (stdArgs { maxSuccess = 1 }) ) |]) runTests = $( [| $(forAllProperties) (quickCheckWithResult (stdArgs { maxSuccess = 1 }) ) |])

View File

@ -89,6 +89,8 @@ data Parameters = Parameters {
hasPipefail :: Bool, hasPipefail :: Bool,
-- A linear (bad) analysis of data flow -- A linear (bad) analysis of data flow
variableFlow :: [StackData], variableFlow :: [StackData],
-- A map from Id to Token
idMap :: Map.Map Id Token,
-- A map from Id to parent Token -- A map from Id to parent Token
parentMap :: Map.Map Id Token, parentMap :: Map.Map Id Token,
-- The shell type, such as Bash or Ksh -- The shell type, such as Bash or Ksh
@ -218,6 +220,7 @@ makeParameters spec = params
Sh -> True Sh -> True
Ksh -> containsPipefail root, Ksh -> containsPipefail root,
shellTypeSpecified = isJust (asShellType spec) || isJust (asFallbackShell spec), shellTypeSpecified = isJust (asShellType spec) || isJust (asFallbackShell spec),
idMap = getTokenMap root,
parentMap = getParentTree root, parentMap = getParentTree root,
variableFlow = getVariableFlow params root, variableFlow = getVariableFlow params root,
tokenPositions = asTokenPositions spec, tokenPositions = asTokenPositions spec,

View File

@ -804,6 +804,7 @@ fulfillsDependency ctx entry dep =
-- it won't be found by the normal check. -- it won't be found by the normal check.
DepIsRecursive node val | node == entry -> return True DepIsRecursive node val | node == entry -> return True
DepIsRecursive node val -> return $ val == any (\f -> entryPoint f == node) (cStack ctx) DepIsRecursive node val -> return $ val == any (\f -> entryPoint f == node) (cStack ctx)
DepExitCodes val -> (== val) <$> peekStack (\s k -> sExitCodes s) S.empty ctx ()
-- _ -> error $ "Unknown dep " ++ show dep -- _ -> error $ "Unknown dep " ++ show dep
where where
peek scope = peekStack getVariableWithScope $ if scope == GlobalScope then (unknownVariableState, GlobalScope) else (unsetVariableState, LocalScope) peek scope = peekStack getVariableWithScope $ if scope == GlobalScope then (unknownVariableState, GlobalScope) else (unsetVariableState, LocalScope)