Optionally suggest [[ over [ in Bash scripts (-o require-double-brackets) (fixes #887)

This commit is contained in:
Vidar Holen 2021-07-27 18:53:30 -07:00
parent fbc8d2cb2f
commit fe81dc1c27
3 changed files with 44 additions and 1 deletions

View File

@ -3,6 +3,7 @@
- SC2286-SC2288: Warn when command name ends in a symbol like `/.)'"` - SC2286-SC2288: Warn when command name ends in a symbol like `/.)'"`
- SC2289: Warn when command name contains tabs or linefeeds - SC2289: Warn when command name contains tabs or linefeeds
- SC2291: Warn about repeated unquoted spaces between words in echo - SC2291: Warn about repeated unquoted spaces between words in echo
- SC2292: Suggest [[ over [ in Bash/Ksh scripts (optional)
### 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] ]]

View File

@ -244,6 +244,13 @@ optionalTreeChecks = [
cdPositive = "echo $VAR", cdPositive = "echo $VAR",
cdNegative = "VAR=hello; echo $VAR" cdNegative = "VAR=hello; echo $VAR"
}, checkUnassignedReferences' True) }, checkUnassignedReferences' True)
,(newCheckDescription {
cdName = "require-double-brackets",
cdDescription = "Require [[ and warn about [ in Bash/Ksh",
cdPositive = "[ -e /etc/issue ]",
cdNegative = "[[ -e /etc/issue ]]"
}, checkRequireDoubleBracket)
] ]
optionalCheckMap :: Map.Map String (Parameters -> Token -> [TokenComment]) optionalCheckMap :: Map.Map String (Parameters -> Token -> [TokenComment])
@ -4311,5 +4318,39 @@ checkCommandWithTrailingSymbol _ t =
'\"' -> "doublequote" '\"' -> "doublequote"
x -> '\'' : x : "\'" x -> '\'' : x : "\'"
prop_checkRequireDoubleBracket1 = verifyTree checkRequireDoubleBracket "[ -x foo ]"
prop_checkRequireDoubleBracket2 = verifyTree checkRequireDoubleBracket "[ foo -o bar ]"
prop_checkRequireDoubleBracket3 = verifyNotTree checkRequireDoubleBracket "#!/bin/sh\n[ -x foo ]"
prop_checkRequireDoubleBracket4 = verifyNotTree checkRequireDoubleBracket "[[ -x foo ]]"
checkRequireDoubleBracket params =
if isBashLike params
then nodeChecksToTreeCheck [check] params
else const []
where
check _ t = case t of
T_Condition id SingleBracket _ ->
styleWithFix id 2292 "Prefer [[ ]] over [ ] for tests in Bash/Ksh." (fixFor t)
_ -> return ()
fixFor t = fixWith $
if isSimple t
then
[
replaceStart (getId t) params 0 "[",
replaceEnd (getId t) params 0 "]"
]
else []
-- We don't tag operators like < and -o well enough to replace them,
-- so just handle the simple cases.
isSimple t = case t of
T_Condition _ _ s -> isSimple s
TC_Binary _ _ op _ _ -> not $ any (\x -> x `elem` op) "<>"
TC_Unary {} -> True
TC_Nullary {} -> True
_ -> False
return [] return []
runTests = $( [| $(forAllProperties) (quickCheckWithResult (stdArgs { maxSuccess = 1 }) ) |]) runTests = $( [| $(forAllProperties) (quickCheckWithResult (stdArgs { maxSuccess = 1 }) ) |])

View File

@ -178,7 +178,8 @@ makeCommentWithFix :: Severity -> Id -> Code -> String -> Fix -> TokenComment
makeCommentWithFix severity id code str fix = makeCommentWithFix severity id code str fix =
let comment = makeComment severity id code str let comment = makeComment severity id code str
withFix = comment { withFix = comment {
tcFix = Just fix -- If fix is empty, pretend it wasn't there.
tcFix = if null (fixReplacements fix) then Nothing else Just fix
} }
in force withFix in force withFix