Merge branch 'master' into 1186
This commit is contained in:
commit
407f6a63b9
|
@ -16,6 +16,7 @@
|
||||||
- Associative arrays are now respected in arithmetic contexts
|
- Associative arrays are now respected in arithmetic contexts
|
||||||
- SC1087 about `$var[@]` now correctly triggers on any index
|
- SC1087 about `$var[@]` now correctly triggers on any index
|
||||||
- Bad expansions in here documents are no longer ignored
|
- Bad expansions in here documents are no longer ignored
|
||||||
|
- FD move operations like {fd}>1- now parse correctly
|
||||||
|
|
||||||
### Changed
|
### Changed
|
||||||
- SC1073: 'else if' is now parsed correctly and not like 'elif'
|
- SC1073: 'else if' is now parsed correctly and not like 'elif'
|
||||||
|
|
|
@ -573,6 +573,7 @@ prop_checkRedirectToSame4 = verifyNot checkRedirectToSame "foo /dev/null > /dev/
|
||||||
prop_checkRedirectToSame5 = verifyNot checkRedirectToSame "foo > bar 2> bar"
|
prop_checkRedirectToSame5 = verifyNot checkRedirectToSame "foo > bar 2> bar"
|
||||||
prop_checkRedirectToSame6 = verifyNot checkRedirectToSame "echo foo > foo"
|
prop_checkRedirectToSame6 = verifyNot checkRedirectToSame "echo foo > foo"
|
||||||
prop_checkRedirectToSame7 = verifyNot checkRedirectToSame "sed 's/foo/bar/g' file | sponge file"
|
prop_checkRedirectToSame7 = verifyNot checkRedirectToSame "sed 's/foo/bar/g' file | sponge file"
|
||||||
|
prop_checkRedirectToSame8 = verifyNot checkRedirectToSame "while read -r line; do _=\"$fname\"; done <\"$fname\""
|
||||||
checkRedirectToSame params s@(T_Pipeline _ _ list) =
|
checkRedirectToSame params s@(T_Pipeline _ _ list) =
|
||||||
mapM_ (\l -> (mapM_ (\x -> doAnalysis (checkOccurrences x) l) (getAllRedirs list))) list
|
mapM_ (\l -> (mapM_ (\x -> doAnalysis (checkOccurrences x) l) (getAllRedirs list))) list
|
||||||
where
|
where
|
||||||
|
@ -583,7 +584,8 @@ checkRedirectToSame params s@(T_Pipeline _ _ list) =
|
||||||
&& x == y
|
&& x == y
|
||||||
&& not (isOutput t && isOutput u)
|
&& not (isOutput t && isOutput u)
|
||||||
&& not (special t)
|
&& not (special t)
|
||||||
&& not (any isHarmlessCommand [t,u])) $ do
|
&& not (any isHarmlessCommand [t,u])
|
||||||
|
&& not (any containsAssignment [u])) $ do
|
||||||
addComment $ note newId
|
addComment $ note newId
|
||||||
addComment $ note exceptId
|
addComment $ note exceptId
|
||||||
checkOccurrences _ _ = return ()
|
checkOccurrences _ _ = return ()
|
||||||
|
@ -610,6 +612,9 @@ checkRedirectToSame params s@(T_Pipeline _ _ list) =
|
||||||
cmd <- getClosestCommand (parentMap params) arg
|
cmd <- getClosestCommand (parentMap params) arg
|
||||||
name <- getCommandBasename cmd
|
name <- getCommandBasename cmd
|
||||||
return $ name `elem` ["echo", "printf", "sponge"]
|
return $ name `elem` ["echo", "printf", "sponge"]
|
||||||
|
containsAssignment arg = fromMaybe False $ do
|
||||||
|
cmd <- getClosestCommand (parentMap params) arg
|
||||||
|
return $ isAssignment cmd
|
||||||
|
|
||||||
checkRedirectToSame _ _ = return ()
|
checkRedirectToSame _ _ = return ()
|
||||||
|
|
||||||
|
@ -788,6 +793,8 @@ prop_checkSingleQuotedVariables11= verifyNot checkSingleQuotedVariables "sed '${
|
||||||
prop_checkSingleQuotedVariables12= verifyNot checkSingleQuotedVariables "eval 'echo $1'"
|
prop_checkSingleQuotedVariables12= verifyNot checkSingleQuotedVariables "eval 'echo $1'"
|
||||||
prop_checkSingleQuotedVariables13= verifyNot checkSingleQuotedVariables "busybox awk '{print $1}'"
|
prop_checkSingleQuotedVariables13= verifyNot checkSingleQuotedVariables "busybox awk '{print $1}'"
|
||||||
prop_checkSingleQuotedVariables14= verifyNot checkSingleQuotedVariables "[ -v 'bar[$foo]' ]"
|
prop_checkSingleQuotedVariables14= verifyNot checkSingleQuotedVariables "[ -v 'bar[$foo]' ]"
|
||||||
|
prop_checkSingleQuotedVariables15= verifyNot checkSingleQuotedVariables "git filter-branch 'test $GIT_COMMIT'"
|
||||||
|
prop_checkSingleQuotedVariables16= verify checkSingleQuotedVariables "git '$a'"
|
||||||
checkSingleQuotedVariables params t@(T_SingleQuoted id s) =
|
checkSingleQuotedVariables params t@(T_SingleQuoted id s) =
|
||||||
when (s `matches` re) $
|
when (s `matches` re) $
|
||||||
if "sed" == commandName
|
if "sed" == commandName
|
||||||
|
@ -800,7 +807,7 @@ checkSingleQuotedVariables params t@(T_SingleQuoted id s) =
|
||||||
commandName = fromMaybe "" $ do
|
commandName = fromMaybe "" $ do
|
||||||
cmd <- getClosestCommand parents t
|
cmd <- getClosestCommand parents t
|
||||||
name <- getCommandBasename cmd
|
name <- getCommandBasename cmd
|
||||||
return $ if name == "find" then getFindCommand cmd else name
|
return $ if name == "find" then getFindCommand cmd else if name == "git" then getGitCommand cmd else name
|
||||||
|
|
||||||
isProbablyOk =
|
isProbablyOk =
|
||||||
any isOkAssignment (take 3 $ getPath parents t)
|
any isOkAssignment (take 3 $ getPath parents t)
|
||||||
|
@ -819,6 +826,7 @@ checkSingleQuotedVariables params t@(T_SingleQuoted id s) =
|
||||||
,"dpkg-query"
|
,"dpkg-query"
|
||||||
,"jq" -- could also check that user provides --arg
|
,"jq" -- could also check that user provides --arg
|
||||||
,"unset"
|
,"unset"
|
||||||
|
,"git filter-branch"
|
||||||
]
|
]
|
||||||
|| "awk" `isSuffixOf` commandName
|
|| "awk" `isSuffixOf` commandName
|
||||||
|| "perl" `isPrefixOf` commandName
|
|| "perl" `isPrefixOf` commandName
|
||||||
|
@ -842,6 +850,12 @@ checkSingleQuotedVariables params t@(T_SingleQuoted id s) =
|
||||||
_ -> "find"
|
_ -> "find"
|
||||||
getFindCommand (T_Redirecting _ _ cmd) = getFindCommand cmd
|
getFindCommand (T_Redirecting _ _ cmd) = getFindCommand cmd
|
||||||
getFindCommand _ = "find"
|
getFindCommand _ = "find"
|
||||||
|
getGitCommand (T_SimpleCommand _ _ words) =
|
||||||
|
case map getLiteralString words of
|
||||||
|
Just "git":Just "filter-branch":_ -> "git filter-branch"
|
||||||
|
_ -> "git"
|
||||||
|
getGitCommand (T_Redirecting _ _ cmd) = getGitCommand cmd
|
||||||
|
getGitCommand _ = "git"
|
||||||
checkSingleQuotedVariables _ _ = return ()
|
checkSingleQuotedVariables _ _ = return ()
|
||||||
|
|
||||||
|
|
||||||
|
@ -1402,6 +1416,7 @@ prop_checkSpuriousExec4 = verifyNot checkSpuriousExec "if a; then exec b; fi"
|
||||||
prop_checkSpuriousExec5 = verifyNot checkSpuriousExec "exec > file; cmd"
|
prop_checkSpuriousExec5 = verifyNot checkSpuriousExec "exec > file; cmd"
|
||||||
prop_checkSpuriousExec6 = verify checkSpuriousExec "exec foo > file; cmd"
|
prop_checkSpuriousExec6 = verify checkSpuriousExec "exec foo > file; cmd"
|
||||||
prop_checkSpuriousExec7 = verifyNot checkSpuriousExec "exec file; echo failed; exit 3"
|
prop_checkSpuriousExec7 = verifyNot checkSpuriousExec "exec file; echo failed; exit 3"
|
||||||
|
prop_checkSpuriousExec8 = verifyNot checkSpuriousExec "exec {origout}>&1- >tmp.log 2>&1; bar"
|
||||||
checkSpuriousExec _ = doLists
|
checkSpuriousExec _ = doLists
|
||||||
where
|
where
|
||||||
doLists (T_Script _ _ cmds) = doList cmds
|
doLists (T_Script _ _ cmds) = doList cmds
|
||||||
|
@ -1801,6 +1816,7 @@ prop_checkUnused35= verifyNotTree checkUnusedAssignments "a=foo; b=2; echo ${a:b
|
||||||
prop_checkUnused36= verifyNotTree checkUnusedAssignments "if [[ -v foo ]]; then true; fi"
|
prop_checkUnused36= verifyNotTree checkUnusedAssignments "if [[ -v foo ]]; then true; fi"
|
||||||
prop_checkUnused37= verifyNotTree checkUnusedAssignments "fd=2; exec {fd}>&-"
|
prop_checkUnused37= verifyNotTree checkUnusedAssignments "fd=2; exec {fd}>&-"
|
||||||
prop_checkUnused38= verifyTree checkUnusedAssignments "(( a=42 ))"
|
prop_checkUnused38= verifyTree checkUnusedAssignments "(( a=42 ))"
|
||||||
|
prop_checkUnused39= verifyNotTree checkUnusedAssignments "declare -x -f foo"
|
||||||
checkUnusedAssignments params t = execWriter (mapM_ warnFor unused)
|
checkUnusedAssignments params t = execWriter (mapM_ warnFor unused)
|
||||||
where
|
where
|
||||||
flow = variableFlow params
|
flow = variableFlow params
|
||||||
|
@ -1818,7 +1834,7 @@ checkUnusedAssignments params t = execWriter (mapM_ warnFor unused)
|
||||||
|
|
||||||
warnFor (name, token) =
|
warnFor (name, token) =
|
||||||
warn (getId token) 2034 $
|
warn (getId token) 2034 $
|
||||||
name ++ " appears unused. Verify it or export it."
|
name ++ " appears unused. Verify use (or export if used externally)."
|
||||||
|
|
||||||
stripSuffix = takeWhile isVariableChar
|
stripSuffix = takeWhile isVariableChar
|
||||||
defaultMap = Map.fromList $ zip internalVariables $ repeat ()
|
defaultMap = Map.fromList $ zip internalVariables $ repeat ()
|
||||||
|
|
|
@ -498,7 +498,9 @@ getReferencedVariableCommand base@(T_SimpleCommand _ _ (T_NormalWord _ (T_Litera
|
||||||
"export" -> if "f" `elem` flags
|
"export" -> if "f" `elem` flags
|
||||||
then []
|
then []
|
||||||
else concatMap getReference rest
|
else concatMap getReference rest
|
||||||
"declare" -> if any (`elem` flags) ["x", "p"]
|
"declare" -> if
|
||||||
|
any (`elem` flags) ["x", "p"] &&
|
||||||
|
(not $ any (`elem` flags) ["f", "F"])
|
||||||
then concatMap getReference rest
|
then concatMap getReference rest
|
||||||
else []
|
else []
|
||||||
"readonly" ->
|
"readonly" ->
|
||||||
|
|
|
@ -513,6 +513,8 @@ prop_checkPrintfVar10= verifyNot checkPrintfVar "printf '%s %s %s' foo bar baz"
|
||||||
prop_checkPrintfVar11= verifyNot checkPrintfVar "printf '%(%s%s)T' -1"
|
prop_checkPrintfVar11= verifyNot checkPrintfVar "printf '%(%s%s)T' -1"
|
||||||
prop_checkPrintfVar12= verify checkPrintfVar "printf '%s %s\\n' 1 2 3"
|
prop_checkPrintfVar12= verify checkPrintfVar "printf '%s %s\\n' 1 2 3"
|
||||||
prop_checkPrintfVar13= verifyNot checkPrintfVar "printf '%s %s\\n' 1 2 3 4"
|
prop_checkPrintfVar13= verifyNot checkPrintfVar "printf '%s %s\\n' 1 2 3 4"
|
||||||
|
prop_checkPrintfVar14= verify checkPrintfVar "printf '%*s\\n' 1"
|
||||||
|
prop_checkPrintfVar15= verifyNot checkPrintfVar "printf '%*s\\n' 1 2"
|
||||||
checkPrintfVar = CommandCheck (Exactly "printf") (f . arguments) where
|
checkPrintfVar = CommandCheck (Exactly "printf") (f . arguments) where
|
||||||
f (doubledash:rest) | getLiteralString doubledash == Just "--" = f rest
|
f (doubledash:rest) | getLiteralString doubledash == Just "--" = f rest
|
||||||
f (dashv:var:rest) | getLiteralString dashv == Just "-v" = f rest
|
f (dashv:var:rest) | getLiteralString dashv == Just "-v" = f rest
|
||||||
|
@ -523,6 +525,7 @@ checkPrintfVar = CommandCheck (Exactly "printf") (f . arguments) where
|
||||||
case string of
|
case string of
|
||||||
'%':'%':rest -> countFormats rest
|
'%':'%':rest -> countFormats rest
|
||||||
'%':'(':rest -> 1 + countFormats (dropWhile (/= ')') rest)
|
'%':'(':rest -> 1 + countFormats (dropWhile (/= ')') rest)
|
||||||
|
'%':'*':rest -> 2 + countFormats rest -- width is specified as an argument
|
||||||
'%':rest -> 1 + countFormats rest
|
'%':rest -> 1 + countFormats rest
|
||||||
_:rest -> countFormats rest
|
_:rest -> countFormats rest
|
||||||
[] -> 0
|
[] -> 0
|
||||||
|
|
|
@ -1223,12 +1223,6 @@ doubleQuotedPart = readDoubleLiteral <|> readDoubleQuotedDollar <|> readQuotedBa
|
||||||
"This is a unicode quote. Delete and retype it (or ignore/singlequote for literal)."
|
"This is a unicode quote. Delete and retype it (or ignore/singlequote for literal)."
|
||||||
return $ T_Literal id [c]
|
return $ T_Literal id [c]
|
||||||
|
|
||||||
readDoubleQuotedLiteral = do
|
|
||||||
doubleQuote
|
|
||||||
x <- readDoubleLiteral
|
|
||||||
doubleQuote
|
|
||||||
return x
|
|
||||||
|
|
||||||
readDoubleLiteral = do
|
readDoubleLiteral = do
|
||||||
id <- getNextId
|
id <- getNextId
|
||||||
s <- many1 readDoubleLiteralPart
|
s <- many1 readDoubleLiteralPart
|
||||||
|
@ -1716,8 +1710,15 @@ readIoFileOp = choice [g_DGREAT, g_LESSGREAT, g_GREATAND, g_LESSAND, g_CLOBBER,
|
||||||
readIoDuplicate = try $ do
|
readIoDuplicate = try $ do
|
||||||
id <- getNextId
|
id <- getNextId
|
||||||
op <- g_GREATAND <|> g_LESSAND
|
op <- g_GREATAND <|> g_LESSAND
|
||||||
target <- readIoVariable <|> many1 digit <|> string "-"
|
target <- readIoVariable <|> digitsAndOrDash
|
||||||
return $ T_IoDuplicate id op target
|
return $ T_IoDuplicate id op target
|
||||||
|
where
|
||||||
|
-- either digits with optional dash, or a required dash
|
||||||
|
digitsAndOrDash = do
|
||||||
|
str <- many digit
|
||||||
|
dash <- (if null str then id else option "") $ string "-"
|
||||||
|
return $ str ++ dash
|
||||||
|
|
||||||
|
|
||||||
prop_readIoFile = isOk readIoFile ">> \"$(date +%YYmmDD)\""
|
prop_readIoFile = isOk readIoFile ">> \"$(date +%YYmmDD)\""
|
||||||
readIoFile = called "redirection" $ do
|
readIoFile = called "redirection" $ do
|
||||||
|
@ -1744,6 +1745,7 @@ prop_readIoRedirect3 = isOk readIoRedirect "4>&-"
|
||||||
prop_readIoRedirect4 = isOk readIoRedirect "&> lol"
|
prop_readIoRedirect4 = isOk readIoRedirect "&> lol"
|
||||||
prop_readIoRedirect5 = isOk readIoRedirect "{foo}>&2"
|
prop_readIoRedirect5 = isOk readIoRedirect "{foo}>&2"
|
||||||
prop_readIoRedirect6 = isOk readIoRedirect "{foo}<&-"
|
prop_readIoRedirect6 = isOk readIoRedirect "{foo}<&-"
|
||||||
|
prop_readIoRedirect7 = isOk readIoRedirect "{foo}>&1-"
|
||||||
readIoRedirect = do
|
readIoRedirect = do
|
||||||
id <- getNextId
|
id <- getNextId
|
||||||
n <- readIoSource
|
n <- readIoSource
|
||||||
|
|
Loading…
Reference in New Issue