Don't warn about repeated range in [[ -v arr[xxx] ]] (fixes #2285)

This commit is contained in:
Vidar Holen 2021-07-25 12:59:56 -07:00
parent 9eb63c97e6
commit 0d58337cdd
3 changed files with 16 additions and 4 deletions

View File

@ -4,6 +4,7 @@
- SC2289: Warn when command name contains tabs or linefeeds - SC2289: Warn when command name contains tabs or linefeeds
### Fixed ### Fixed
- SC2102 about repetitions in ranges no longer triggers on [[ -v arr[xx] ]]
- 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+
### Changed ### Changed

View File

@ -2519,8 +2519,10 @@ 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 [a-zA-Z]" -- tr has 2060
prop_checkCharRangeGlob6 = verifyNot checkCharRangeGlob "[[ $x == [!!]* ]]" prop_checkCharRangeGlob6 = verifyNot checkCharRangeGlob "[[ $x == [!!]* ]]"
prop_checkCharRangeGlob7 = verifyNot checkCharRangeGlob "[[ -v arr[keykey] ]]"
prop_checkCharRangeGlob8 = verifyNot checkCharRangeGlob "[[ arr[keykey] -gt 1 ]]"
checkCharRangeGlob p t@(T_Glob id str) | checkCharRangeGlob p t@(T_Glob id str) |
isCharClass str && not (isParamTo (parentMap p) "tr" t) = isCharClass str && not (isParamTo (parentMap p) "tr" t) && not (isDereferenced t) =
if ":" `isPrefixOf` contents if ":" `isPrefixOf` contents
&& ":" `isSuffixOf` contents && ":" `isSuffixOf` contents
&& contents /= ":" && contents /= ":"
@ -2537,6 +2539,15 @@ checkCharRangeGlob p t@(T_Glob id str) |
'!':rest -> rest '!':rest -> rest
'^':rest -> rest '^':rest -> rest
x -> x x -> x
-- Check if this is a dereferencing context like [[ -v array[operandhere] ]]
isDereferenced = fromMaybe False . msum . map isDereferencingOp . getPath (parentMap p)
isDereferencingOp t =
case t of
TC_Binary _ DoubleBracket str _ _ -> return $ isDereferencingBinaryOp str
TC_Unary _ _ str _ -> return $ str == "-v"
T_SimpleCommand {} -> return False
_ -> Nothing
checkCharRangeGlob _ _ = return () checkCharRangeGlob _ _ = return ()

View File

@ -737,7 +737,7 @@ getReferencedVariables parents t =
TC_Unary id _ "-v" token -> getIfReference t token TC_Unary id _ "-v" token -> getIfReference t token
TC_Unary id _ "-R" token -> getIfReference t token TC_Unary id _ "-R" token -> getIfReference t token
TC_Binary id DoubleBracket op lhs rhs -> TC_Binary id DoubleBracket op lhs rhs ->
if isDereferencing op if isDereferencingBinaryOp op
then concatMap (getIfReference t) [lhs, rhs] then concatMap (getIfReference t) [lhs, rhs]
else [] else []
@ -771,12 +771,12 @@ getReferencedVariables parents t =
when (isDigit h) $ fail "is a number" when (isDigit h) $ fail "is a number"
return (context, token, getBracedReference str) return (context, token, getBracedReference str)
isDereferencing = (`elem` ["-eq", "-ne", "-lt", "-le", "-gt", "-ge"])
isArithmeticAssignment t = case getPath parents t of isArithmeticAssignment t = case getPath parents t of
this: TA_Assignment _ "=" lhs _ :_ -> lhs == t this: TA_Assignment _ "=" lhs _ :_ -> lhs == t
_ -> False _ -> False
isDereferencingBinaryOp = (`elem` ["-eq", "-ne", "-lt", "-le", "-gt", "-ge"])
dataTypeFrom defaultType v = (case v of T_Array {} -> DataArray; _ -> defaultType) $ SourceFrom [v] dataTypeFrom defaultType v = (case v of T_Array {} -> DataArray; _ -> defaultType) $ SourceFrom [v]