Warn about `read foo[i]` expanding as glob (fixes #2345)
This commit is contained in:
parent
05bdeae3ab
commit
205ba429b3
|
@ -17,6 +17,7 @@
|
||||||
- SC2304-SC2306: Warn about unquoted globs in expr arguments
|
- SC2304-SC2306: Warn about unquoted globs in expr arguments
|
||||||
- SC2307: Warn about insufficient number of arguments to expr
|
- SC2307: Warn about insufficient number of arguments to expr
|
||||||
- SC2308: Suggest other approaches for non-standard expr extensions
|
- SC2308: Suggest other approaches for non-standard expr extensions
|
||||||
|
- SC2313: Warn about `read` with unquoted, array indexed variable
|
||||||
|
|
||||||
### 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] ]]
|
||||||
|
|
|
@ -2689,12 +2689,13 @@ prop_checkCharRangeGlob1 = verify checkCharRangeGlob "ls *[:digit:].jpg"
|
||||||
prop_checkCharRangeGlob2 = verifyNot checkCharRangeGlob "ls *[[:digit:]].jpg"
|
prop_checkCharRangeGlob2 = verifyNot checkCharRangeGlob "ls *[[:digit:]].jpg"
|
||||||
prop_checkCharRangeGlob3 = verify checkCharRangeGlob "ls [10-15]"
|
prop_checkCharRangeGlob3 = verify checkCharRangeGlob "ls [10-15]"
|
||||||
prop_checkCharRangeGlob4 = verifyNot checkCharRangeGlob "ls [a-zA-Z]"
|
prop_checkCharRangeGlob4 = verifyNot checkCharRangeGlob "ls [a-zA-Z]"
|
||||||
prop_checkCharRangeGlob5 = verifyNot checkCharRangeGlob "tr -d [a-zA-Z]" -- tr has 2060
|
prop_checkCharRangeGlob5 = verifyNot checkCharRangeGlob "tr -d [aa]" -- tr has 2060
|
||||||
prop_checkCharRangeGlob6 = verifyNot checkCharRangeGlob "[[ $x == [!!]* ]]"
|
prop_checkCharRangeGlob6 = verifyNot checkCharRangeGlob "[[ $x == [!!]* ]]"
|
||||||
prop_checkCharRangeGlob7 = verifyNot checkCharRangeGlob "[[ -v arr[keykey] ]]"
|
prop_checkCharRangeGlob7 = verifyNot checkCharRangeGlob "[[ -v arr[keykey] ]]"
|
||||||
prop_checkCharRangeGlob8 = verifyNot checkCharRangeGlob "[[ arr[keykey] -gt 1 ]]"
|
prop_checkCharRangeGlob8 = verifyNot checkCharRangeGlob "[[ arr[keykey] -gt 1 ]]"
|
||||||
|
prop_checkCharRangeGlob9 = verifyNot checkCharRangeGlob "read arr[keykey]" -- tr has 2313
|
||||||
checkCharRangeGlob p t@(T_Glob id str) |
|
checkCharRangeGlob p t@(T_Glob id str) |
|
||||||
isCharClass str && not (isParamTo (parentMap p) "tr" t) && not (isDereferenced t) =
|
isCharClass str && not isIgnoredCommand && not (isDereferenced t) =
|
||||||
if ":" `isPrefixOf` contents
|
if ":" `isPrefixOf` contents
|
||||||
&& ":" `isSuffixOf` contents
|
&& ":" `isSuffixOf` contents
|
||||||
&& contents /= ":"
|
&& contents /= ":"
|
||||||
|
@ -2712,6 +2713,10 @@ checkCharRangeGlob p t@(T_Glob id str) |
|
||||||
'^':rest -> rest
|
'^':rest -> rest
|
||||||
x -> x
|
x -> x
|
||||||
|
|
||||||
|
isIgnoredCommand = fromMaybe False $ do
|
||||||
|
cmd <- getClosestCommand (parentMap p) t
|
||||||
|
return $ isCommandMatch cmd (`elem` ["tr", "read"])
|
||||||
|
|
||||||
-- Check if this is a dereferencing context like [[ -v array[operandhere] ]]
|
-- Check if this is a dereferencing context like [[ -v array[operandhere] ]]
|
||||||
isDereferenced = fromMaybe False . msum . map isDereferencingOp . getPath (parentMap p)
|
isDereferenced = fromMaybe False . msum . map isDereferencingOp . getPath (parentMap p)
|
||||||
isDereferencingOp t =
|
isDereferencingOp t =
|
||||||
|
|
|
@ -790,6 +790,7 @@ prop_checkReadExpansions5 = verify checkReadExpansions "read \"$var\""
|
||||||
prop_checkReadExpansions6 = verify checkReadExpansions "read -a $var"
|
prop_checkReadExpansions6 = verify checkReadExpansions "read -a $var"
|
||||||
prop_checkReadExpansions7 = verifyNot checkReadExpansions "read $1"
|
prop_checkReadExpansions7 = verifyNot checkReadExpansions "read $1"
|
||||||
prop_checkReadExpansions8 = verifyNot checkReadExpansions "read ${var?}"
|
prop_checkReadExpansions8 = verifyNot checkReadExpansions "read ${var?}"
|
||||||
|
prop_checkReadExpansions9 = verify checkReadExpansions "read arr[val]"
|
||||||
checkReadExpansions = CommandCheck (Exactly "read") check
|
checkReadExpansions = CommandCheck (Exactly "read") check
|
||||||
where
|
where
|
||||||
options = getGnuOpts flagsForRead
|
options = getGnuOpts flagsForRead
|
||||||
|
@ -797,13 +798,26 @@ checkReadExpansions = CommandCheck (Exactly "read") check
|
||||||
opts <- options $ arguments cmd
|
opts <- options $ arguments cmd
|
||||||
return [y | (x,(_, y)) <- opts, null x || x == "a"]
|
return [y | (x,(_, y)) <- opts, null x || x == "a"]
|
||||||
|
|
||||||
check cmd = mapM_ warning $ getVars cmd
|
check cmd = do
|
||||||
warning t = sequence_ $ do
|
mapM_ dollarWarning $ getVars cmd
|
||||||
|
mapM_ arrayWarning $ arguments cmd
|
||||||
|
|
||||||
|
dollarWarning t = sequence_ $ do
|
||||||
name <- getSingleUnmodifiedBracedString t
|
name <- getSingleUnmodifiedBracedString t
|
||||||
guard $ isVariableName name -- e.g. not $1
|
guard $ isVariableName name -- e.g. not $1
|
||||||
return . warn (getId t) 2229 $
|
return . warn (getId t) 2229 $
|
||||||
"This does not read '" ++ name ++ "'. Remove $/${} for that, or use ${var?} to quiet."
|
"This does not read '" ++ name ++ "'. Remove $/${} for that, or use ${var?} to quiet."
|
||||||
|
|
||||||
|
arrayWarning word =
|
||||||
|
when (any isUnquotedBracket $ getWordParts word) $
|
||||||
|
warn (getId word) 2313 $
|
||||||
|
"Quote array indices to avoid them expanding as globs."
|
||||||
|
|
||||||
|
isUnquotedBracket t =
|
||||||
|
case t of
|
||||||
|
T_Glob _ ('[':_) -> True
|
||||||
|
_ -> False
|
||||||
|
|
||||||
-- Return the single variable expansion that makes up this word, if any.
|
-- Return the single variable expansion that makes up this word, if any.
|
||||||
-- e.g. $foo -> $foo, "$foo"'' -> $foo , "hello $name" -> Nothing
|
-- e.g. $foo -> $foo, "$foo"'' -> $foo , "hello $name" -> Nothing
|
||||||
getSingleUnmodifiedBracedString :: Token -> Maybe String
|
getSingleUnmodifiedBracedString :: Token -> Maybe String
|
||||||
|
|
Loading…
Reference in New Issue