Have SC2155 trigger on 'typeset' as well (fixes #2262)

This commit is contained in:
Vidar Holen 2021-07-25 17:31:13 -07:00
parent 364c33395e
commit 44471b73cc
3 changed files with 63 additions and 31 deletions

View File

@ -5,6 +5,7 @@
### Fixed ### Fixed
- SC2102 about repetitions in ranges no longer triggers on [[ -v arr[xx] ]] - SC2102 about repetitions in ranges no longer triggers on [[ -v arr[xx] ]]
- SC2155 now recognizes `typeset` and local read-only `declare` statements
- SC2290: Warn about misused = in declare & co, which were not caught by SC2270+ - SC2290: Warn about misused = in declare & co, which were not caught by SC2270+
- The flag --color=auto no longer outputs color when TERM is "dumb" or unset - The flag --color=auto no longer outputs color when TERM is "dumb" or unset

View File

@ -169,7 +169,6 @@ nodeChecks = [
,checkTestArgumentSplitting ,checkTestArgumentSplitting
,checkConcatenatedDollarAt ,checkConcatenatedDollarAt
,checkTildeInPath ,checkTildeInPath
,checkMaskedReturns
,checkReadWithoutR ,checkReadWithoutR
,checkLoopVariableReassignment ,checkLoopVariableReassignment
,checkTrailingBracket ,checkTrailingBracket
@ -2970,31 +2969,6 @@ checkTestArgumentSplitting params t =
err (getId token) 2255 "[ ] does not apply arithmetic evaluation. Evaluate with $((..)) for numbers, or use string comparator for strings." err (getId token) 2255 "[ ] does not apply arithmetic evaluation. Evaluate with $((..)) for numbers, or use string comparator for strings."
prop_checkMaskedReturns1 = verify checkMaskedReturns "f() { local a=$(false); }"
prop_checkMaskedReturns2 = verify checkMaskedReturns "declare a=$(false)"
prop_checkMaskedReturns3 = verify checkMaskedReturns "declare a=\"`false`\""
prop_checkMaskedReturns4 = verify checkMaskedReturns "readonly a=$(false)"
prop_checkMaskedReturns5 = verify checkMaskedReturns "readonly a=\"`false`\""
prop_checkMaskedReturns6 = verifyNot checkMaskedReturns "declare a; a=$(false)"
prop_checkMaskedReturns7 = verifyNot checkMaskedReturns "f() { local -r a=$(false); }"
prop_checkMaskedReturns8 = verifyNot checkMaskedReturns "a=$(false); readonly a"
checkMaskedReturns _ t@(T_SimpleCommand id _ (cmd:rest)) = sequence_ $ do
name <- getCommandName t
guard $ name `elem` ["declare", "export", "readonly"]
|| name == "local" && "r" `notElem` map snd (getAllFlags t)
return $ mapM_ checkArgs rest
where
checkArgs (T_Assignment id _ _ _ word) | any hasReturn $ getWordParts word =
warn id 2155 "Declare and assign separately to avoid masking return values."
checkArgs _ = return ()
hasReturn t = case t of
T_Backticked {} -> True
T_DollarExpansion {} -> True
_ -> False
checkMaskedReturns _ _ = return ()
prop_checkReadWithoutR1 = verify checkReadWithoutR "read -a foo" prop_checkReadWithoutR1 = verify checkReadWithoutR "read -a foo"
prop_checkReadWithoutR2 = verifyNot checkReadWithoutR "read -ar foo" prop_checkReadWithoutR2 = verifyNot checkReadWithoutR "read -ar foo"
prop_checkReadWithoutR3 = verifyNot checkReadWithoutR "read -t 0" prop_checkReadWithoutR3 = verifyNot checkReadWithoutR "read -t 0"

View File

@ -95,12 +95,12 @@ commandChecks = [
,checkSourceArgs ,checkSourceArgs
,checkChmodDashr ,checkChmodDashr
,checkXargsDashi ,checkXargsDashi
,checkArgComparison "local"
,checkArgComparison "declare"
,checkArgComparison "export"
,checkArgComparison "readonly"
,checkArgComparison "typeset"
] ]
++ map checkArgComparison declaringCommands
++ map checkMaskedReturns declaringCommands
declaringCommands = ["local", "declare", "export", "readonly", "typeset"]
optionalChecks = map fst optionalCommandChecks optionalChecks = map fst optionalCommandChecks
optionalCommandChecks :: [(CheckDescription, CommandCheck)] optionalCommandChecks :: [(CheckDescription, CommandCheck)]
@ -1174,5 +1174,62 @@ checkArgComparison str = CommandCheck (Exactly str) wordsWithEqual
T_NormalWord _ (x:_) -> getId x T_NormalWord _ (x:_) -> getId x
_ -> getId t _ -> getId t
prop_checkMaskedReturns1 = verify (checkMaskedReturns "local") "f() { local a=$(false); }"
prop_checkMaskedReturns2 = verify (checkMaskedReturns "declare") "declare a=$(false)"
prop_checkMaskedReturns3 = verify (checkMaskedReturns "declare") "declare a=\"`false`\""
prop_checkMaskedReturns4 = verify (checkMaskedReturns "readonly") "readonly a=$(false)"
prop_checkMaskedReturns5 = verify (checkMaskedReturns "readonly") "readonly a=\"`false`\""
prop_checkMaskedReturns6 = verifyNot (checkMaskedReturns "declare") "declare a; a=$(false)"
prop_checkMaskedReturns7 = verifyNot (checkMaskedReturns "local") "f() { local -r a=$(false); }"
prop_checkMaskedReturns8 = verifyNot (checkMaskedReturns "readonly") "a=$(false); readonly a"
prop_checkMaskedReturns9 = verify (checkMaskedReturns "typeset") "#!/bin/ksh\n f() { typeset -r x=$(false); }"
prop_checkMaskedReturns10 = verifyNot (checkMaskedReturns "typeset") "#!/bin/ksh\n function f { typeset -r x=$(false); }"
prop_checkMaskedReturns11 = verifyNot (checkMaskedReturns "typeset") "#!/bin/bash\n f() { typeset -r x=$(false); }"
prop_checkMaskedReturns12 = verify (checkMaskedReturns "typeset") "typeset -r x=$(false);"
prop_checkMaskedReturns13 = verify (checkMaskedReturns "typeset") "f() { typeset -g x=$(false); }"
prop_checkMaskedReturns14 = verify (checkMaskedReturns "declare") "declare x=${ false; }"
prop_checkMaskedReturns15 = verify (checkMaskedReturns "declare") "f() { declare x=$(false); }"
checkMaskedReturns str = CommandCheck (Exactly str) checkCmd
where
checkCmd t = do
path <- getPathM t
shell <- asks shellType
sequence_ $ do
name <- getCommandName t
let flags = map snd (getAllFlags t)
let hasDashR = "r" `elem` flags
let hasDashG = "g" `elem` flags
let isInScopedFunction = any (isScopedFunction shell) path
let isLocal = not hasDashG && isLocalInFunction name && isInScopedFunction
let isReadOnly = name == "readonly" || hasDashR
-- Don't warn about local variables that are declared readonly,
-- because the workaround `local x; x=$(false); local -r x;` is annoying
guard . not $ isLocal && isReadOnly
return $ mapM_ checkArgs $ arguments t
checkArgs (T_Assignment id _ _ _ word) | any hasReturn $ getWordParts word =
warn id 2155 "Declare and assign separately to avoid masking return values."
checkArgs _ = return ()
isLocalInFunction = (`elem` ["local", "declare", "typeset"])
isScopedFunction shell t =
case t of
T_BatsTest {} -> True
-- In ksh, only functions declared with 'function' have their own scope
T_Function _ (FunctionKeyword hasFunction) _ _ _ -> shell /= Ksh || hasFunction
_ -> False
hasReturn t = case t of
T_Backticked {} -> True
T_DollarExpansion {} -> True
T_DollarBraceCommandExpansion {} -> True
_ -> False
return [] return []
runTests = $( [| $(forAllProperties) (quickCheckWithResult (stdArgs { maxSuccess = 1 }) ) |]) runTests = $( [| $(forAllProperties) (quickCheckWithResult (stdArgs { maxSuccess = 1 }) ) |])