mirror of
https://github.com/koalaman/shellcheck
synced 2025-07-16 10:03:08 -07:00
Merge branch 'master' of https://github.com/koalaman/shellcheck into mrshu/pushd-popd-like-cd
Signed-off-by: mr.Shu <mr@shu.io>
This commit is contained in:
commit
79872f92f8
7 changed files with 400 additions and 165 deletions
|
@ -143,7 +143,6 @@ nodeChecks = [
|
|||
,checkWrongArithmeticAssignment
|
||||
,checkConditionalAndOrs
|
||||
,checkFunctionDeclarations
|
||||
,checkCatastrophicRm
|
||||
,checkStderrPipe
|
||||
,checkOverridingPath
|
||||
,checkArrayAsString
|
||||
|
@ -661,15 +660,12 @@ prop_checkUnquotedDollarAt6 = verifyNot checkUnquotedDollarAt "a=$@"
|
|||
prop_checkUnquotedDollarAt7 = verify checkUnquotedDollarAt "for f in ${var[@]}; do true; done"
|
||||
prop_checkUnquotedDollarAt8 = verifyNot checkUnquotedDollarAt "echo \"${args[@]:+${args[@]}}\""
|
||||
prop_checkUnquotedDollarAt9 = verifyNot checkUnquotedDollarAt "echo ${args[@]:+\"${args[@]}\"}"
|
||||
prop_checkUnquotedDollarAt10 = verifyNot checkUnquotedDollarAt "echo ${@+\"$@\"}"
|
||||
checkUnquotedDollarAt p word@(T_NormalWord _ parts) | not $ isStrictlyQuoteFree (parentMap p) word =
|
||||
forM_ (take 1 $ filter isArrayExpansion parts) $ \x ->
|
||||
unless (isAlternative x) $
|
||||
unless (isQuotedAlternativeReference x) $
|
||||
err (getId x) 2068
|
||||
"Double quote array expansions to avoid re-splitting elements."
|
||||
where
|
||||
-- Fixme: should detect whether the alternative is quoted
|
||||
isAlternative b@(T_DollarBraced _ t) = ":+" `isInfixOf` bracedString b
|
||||
isAlternative _ = False
|
||||
checkUnquotedDollarAt _ _ = return ()
|
||||
|
||||
prop_checkConcatenatedDollarAt1 = verify checkConcatenatedDollarAt "echo \"foo$@\""
|
||||
|
@ -1375,10 +1371,11 @@ prop_checkInexplicablyUnquoted4 = verify checkInexplicablyUnquoted "echo \"VALUE
|
|||
prop_checkInexplicablyUnquoted5 = verifyNot checkInexplicablyUnquoted "\"$dir\"/\"$file\""
|
||||
prop_checkInexplicablyUnquoted6 = verifyNot checkInexplicablyUnquoted "\"$dir\"some_stuff\"$file\""
|
||||
prop_checkInexplicablyUnquoted7 = verifyNot checkInexplicablyUnquoted "${dir/\"foo\"/\"bar\"}"
|
||||
prop_checkInexplicablyUnquoted8 = verifyNot checkInexplicablyUnquoted " 'foo'\\\n 'bar'"
|
||||
checkInexplicablyUnquoted _ (T_NormalWord id tokens) = mapM_ check (tails tokens)
|
||||
where
|
||||
check (T_SingleQuoted _ _:T_Literal id str:_)
|
||||
| all isAlphaNum str =
|
||||
| not (null str) && all isAlphaNum str =
|
||||
info id 2026 "This word is outside of quotes. Did you intend to 'nest '\"'single quotes'\"' instead'? "
|
||||
|
||||
check (T_DoubleQuoted _ a:trapped:T_DoubleQuoted _ b:_) =
|
||||
|
@ -1527,6 +1524,7 @@ prop_subshellAssignmentCheck15 = verifyNotTree subshellAssignmentCheck "#!/bin/k
|
|||
prop_subshellAssignmentCheck16 = verifyNotTree subshellAssignmentCheck "(set -e); echo $@"
|
||||
prop_subshellAssignmentCheck17 = verifyNotTree subshellAssignmentCheck "foo=${ { bar=$(baz); } 2>&1; }; echo $foo $bar"
|
||||
prop_subshellAssignmentCheck18 = verifyTree subshellAssignmentCheck "( exec {n}>&2; ); echo $n"
|
||||
prop_subshellAssignmentCheck19 = verifyNotTree subshellAssignmentCheck "#!/bin/bash\nshopt -s lastpipe; echo a | read -r b; echo \"$b\""
|
||||
subshellAssignmentCheck params t =
|
||||
let flow = variableFlow params
|
||||
check = findSubshelled flow [("oops",[])] Map.empty
|
||||
|
@ -1611,6 +1609,7 @@ prop_checkSpacefulness31= verifyNotTree checkSpacefulness "echo \"`echo \\\"$1\\
|
|||
prop_checkSpacefulness32= verifyNotTree checkSpacefulness "var=$1; [ -v var ]"
|
||||
prop_checkSpacefulness33= verifyTree checkSpacefulness "for file; do echo $file; done"
|
||||
prop_checkSpacefulness34= verifyTree checkSpacefulness "declare foo$n=$1"
|
||||
prop_checkSpacefulness35= verifyNotTree checkSpacefulness "echo ${1+\"$1\"}"
|
||||
|
||||
checkSpacefulness params t =
|
||||
doVariableFlowAnalysis readF writeF (Map.fromList defaults) (variableFlow params)
|
||||
|
@ -2110,7 +2109,7 @@ checkLoopKeywordScope params t |
|
|||
where
|
||||
name = getCommandName t
|
||||
path = let p = getPath (parentMap params) t in filter relevant p
|
||||
subshellType t = case leadType (shellType params) (parentMap params) t of
|
||||
subshellType t = case leadType params t of
|
||||
NoneScope -> Nothing
|
||||
SubshellScope str -> return str
|
||||
relevant t = isLoop t || isFunction t || isJust (subshellType t)
|
||||
|
@ -2139,72 +2138,6 @@ checkFunctionDeclarations params
|
|||
checkFunctionDeclarations _ _ = return ()
|
||||
|
||||
|
||||
prop_checkCatastrophicRm1 = verify checkCatastrophicRm "rm -r $1/$2"
|
||||
prop_checkCatastrophicRm2 = verify checkCatastrophicRm "rm -r /home/$foo"
|
||||
prop_checkCatastrophicRm3 = verifyNot checkCatastrophicRm "rm -r /home/${USER:?}/*"
|
||||
prop_checkCatastrophicRm4 = verify checkCatastrophicRm "rm -fr /home/$(whoami)/*"
|
||||
prop_checkCatastrophicRm5 = verifyNot checkCatastrophicRm "rm -r /home/${USER:-thing}/*"
|
||||
prop_checkCatastrophicRm6 = verify checkCatastrophicRm "rm --recursive /etc/*$config*"
|
||||
prop_checkCatastrophicRm8 = verify checkCatastrophicRm "rm -rf /home"
|
||||
prop_checkCatastrophicRm9 = verifyNot checkCatastrophicRm "rm -rf -- /home"
|
||||
prop_checkCatastrophicRm10= verifyNot checkCatastrophicRm "rm -r \"${DIR}\"/{.gitignore,.gitattributes,ci}"
|
||||
prop_checkCatastrophicRm11= verify checkCatastrophicRm "rm -r /{bin,sbin}/$exec"
|
||||
prop_checkCatastrophicRm12= verify checkCatastrophicRm "rm -r /{{usr,},{bin,sbin}}/$exec"
|
||||
prop_checkCatastrophicRm13= verifyNot checkCatastrophicRm "rm -r /{{a,b},{c,d}}/$exec"
|
||||
prop_checkCatastrophicRmA = verify checkCatastrophicRm "rm -rf /usr /lib/nvidia-current/xorg/xorg"
|
||||
prop_checkCatastrophicRmB = verify checkCatastrophicRm "rm -rf \"$STEAMROOT/\"*"
|
||||
checkCatastrophicRm params t@(T_SimpleCommand id _ tokens) | t `isCommand` "rm" =
|
||||
when (any isRecursiveFlag simpleArgs) $
|
||||
mapM_ (mapM_ checkWord . braceExpand) tokens
|
||||
where
|
||||
simpleArgs = oversimplify t
|
||||
|
||||
checkWord token =
|
||||
case getLiteralString token of
|
||||
Just str ->
|
||||
when (notElem "--" simpleArgs && (fixPath str `elem` importantPaths)) $
|
||||
warn (getId token) 2114 "Warning: deletes a system directory. Use 'rm --' to disable this message."
|
||||
Nothing ->
|
||||
checkWord' token
|
||||
|
||||
checkWord' token = fromMaybe (return ()) $ do
|
||||
filename <- getPotentialPath token
|
||||
let path = fixPath filename
|
||||
return . when (path `elem` importantPaths) $
|
||||
warn (getId token) 2115 $ "Use \"${var:?}\" to ensure this never expands to " ++ path ++ " ."
|
||||
|
||||
fixPath filename =
|
||||
let normalized = skipRepeating '/' . skipRepeating '*' $ filename in
|
||||
if normalized == "/" then normalized else stripTrailing '/' normalized
|
||||
|
||||
getPotentialPath = getLiteralStringExt f
|
||||
where
|
||||
f (T_Glob _ str) = return str
|
||||
f (T_DollarBraced _ word) =
|
||||
let var = onlyLiteralString word in
|
||||
if any (`isInfixOf` var) [":?", ":-", ":="]
|
||||
then Nothing
|
||||
else return ""
|
||||
f _ = return ""
|
||||
|
||||
isRecursiveFlag "--recursive" = True
|
||||
isRecursiveFlag ('-':'-':_) = False
|
||||
isRecursiveFlag ('-':str) = 'r' `elem` str || 'R' `elem` str
|
||||
isRecursiveFlag _ = False
|
||||
|
||||
stripTrailing c = reverse . dropWhile (== c) . reverse
|
||||
skipRepeating c (a:b:rest) | a == b && b == c = skipRepeating c (b:rest)
|
||||
skipRepeating c (a:r) = a:skipRepeating c r
|
||||
skipRepeating _ [] = []
|
||||
|
||||
paths = [
|
||||
"", "/bin", "/etc", "/home", "/mnt", "/usr", "/usr/share", "/usr/local",
|
||||
"/var", "/lib"
|
||||
]
|
||||
importantPaths = filter (not . null) $
|
||||
["", "/", "/*", "/*/*"] >>= (\x -> map (++x) paths)
|
||||
checkCatastrophicRm _ _ = return ()
|
||||
|
||||
|
||||
prop_checkStderrPipe1 = verify checkStderrPipe "#!/bin/ksh\nfoo |& bar"
|
||||
prop_checkStderrPipe2 = verifyNot checkStderrPipe "#!/bin/bash\nfoo |& bar"
|
||||
|
@ -2238,7 +2171,7 @@ checkUnpassedInFunctions params root =
|
|||
functions = execWriter $ doAnalysis (tell . maybeToList . findFunction) root
|
||||
|
||||
findFunction t@(T_Function id _ _ name body) =
|
||||
let flow = getVariableFlow (shellType params) (parentMap params) body
|
||||
let flow = getVariableFlow params body
|
||||
in
|
||||
if any (isPositionalReference t) flow && not (any isPositionalAssignment flow)
|
||||
then return t
|
||||
|
@ -2541,7 +2474,9 @@ prop_checkUncheckedCd6 = verifyNotTree checkUncheckedCd "cd .."
|
|||
prop_checkUncheckedCd7 = verifyNotTree checkUncheckedCd "#!/bin/bash -e\ncd foo\nrm bar"
|
||||
prop_checkUncheckedCd8 = verifyNotTree checkUncheckedCd "set -o errexit; cd foo; rm bar"
|
||||
checkUncheckedCd params root =
|
||||
if hasSetE root then [] else execWriter $ doAnalysis checkElement root
|
||||
if hasSetE params
|
||||
then []
|
||||
else execWriter $ doAnalysis checkElement root
|
||||
where
|
||||
checkElement t@T_SimpleCommand {} =
|
||||
when(t `isUnqualifiedCommand` "cd"
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue