Optionally check for unassigned uppercase variables
This commit is contained in:
parent
1297ef46d7
commit
9f0ef5983a
|
@ -8,6 +8,7 @@
|
||||||
- Source paths: Use `-P dir1:dir2` or a `source-path=dir1` directive
|
- Source paths: Use `-P dir1:dir2` or a `source-path=dir1` directive
|
||||||
to specify search paths for sourced files.
|
to specify search paths for sourced files.
|
||||||
- json1 format like --format=json but treats tabs as single characters
|
- json1 format like --format=json but treats tabs as single characters
|
||||||
|
- SC2154: Also warn about unassigned uppercase variables (optional)
|
||||||
- SC2252: Warn about `[ $a != x ] || [ $a != y ]`, similar to SC2055
|
- SC2252: Warn about `[ $a != x ] || [ $a != y ]`, similar to SC2055
|
||||||
- SC2251: Inform about ineffectual ! in front of commands
|
- SC2251: Inform about ineffectual ! in front of commands
|
||||||
- SC2250: Warn about variable references without braces (optional)
|
- SC2250: Warn about variable references without braces (optional)
|
||||||
|
|
|
@ -251,6 +251,9 @@ Here is an example `.shellcheckrc`:
|
||||||
# Turn on warnings for unquoted variables with safe values
|
# Turn on warnings for unquoted variables with safe values
|
||||||
enable=quote-safe-variables
|
enable=quote-safe-variables
|
||||||
|
|
||||||
|
# Turn on warnings for unassigned uppercase variables
|
||||||
|
enable=check-unassigned-uppercase
|
||||||
|
|
||||||
# Allow using `which` since it gives full paths and is common enough
|
# Allow using `which` since it gives full paths and is common enough
|
||||||
disable=SC2230
|
disable=SC2230
|
||||||
|
|
||||||
|
|
|
@ -231,6 +231,13 @@ optionalTreeChecks = [
|
||||||
cdPositive = "var=hello; echo $var",
|
cdPositive = "var=hello; echo $var",
|
||||||
cdNegative = "var=hello; echo ${var}"
|
cdNegative = "var=hello; echo ${var}"
|
||||||
}, nodeChecksToTreeCheck [checkVariableBraces])
|
}, nodeChecksToTreeCheck [checkVariableBraces])
|
||||||
|
|
||||||
|
,(newCheckDescription {
|
||||||
|
cdName = "check-unassigned-uppercase",
|
||||||
|
cdDescription = "Warn when uppercase variables are unassigned",
|
||||||
|
cdPositive = "echo $VAR",
|
||||||
|
cdNegative = "VAR=hello; echo $VAR"
|
||||||
|
}, checkUnassignedReferences' True)
|
||||||
]
|
]
|
||||||
|
|
||||||
optionalCheckMap :: Map.Map String (Parameters -> Token -> [TokenComment])
|
optionalCheckMap :: Map.Map String (Parameters -> Token -> [TokenComment])
|
||||||
|
@ -2131,7 +2138,10 @@ prop_checkUnassignedReferences34= verifyNotTree checkUnassignedReferences "decla
|
||||||
prop_checkUnassignedReferences35= verifyNotTree checkUnassignedReferences "echo ${arr[foo-bar]:?fail}"
|
prop_checkUnassignedReferences35= verifyNotTree checkUnassignedReferences "echo ${arr[foo-bar]:?fail}"
|
||||||
prop_checkUnassignedReferences36= verifyNotTree checkUnassignedReferences "read -a foo -r <<<\"foo bar\"; echo \"$foo\""
|
prop_checkUnassignedReferences36= verifyNotTree checkUnassignedReferences "read -a foo -r <<<\"foo bar\"; echo \"$foo\""
|
||||||
prop_checkUnassignedReferences37= verifyNotTree checkUnassignedReferences "var=howdy; printf -v 'array[0]' %s \"$var\"; printf %s \"${array[0]}\";"
|
prop_checkUnassignedReferences37= verifyNotTree checkUnassignedReferences "var=howdy; printf -v 'array[0]' %s \"$var\"; printf %s \"${array[0]}\";"
|
||||||
checkUnassignedReferences params t = warnings
|
prop_checkUnassignedReferences38= verifyTree (checkUnassignedReferences' True) "echo $VAR"
|
||||||
|
|
||||||
|
checkUnassignedReferences = checkUnassignedReferences' False
|
||||||
|
checkUnassignedReferences' includeGlobals params t = warnings
|
||||||
where
|
where
|
||||||
(readMap, writeMap) = execState (mapM tally $ variableFlow params) (Map.empty, Map.empty)
|
(readMap, writeMap) = execState (mapM tally $ variableFlow params) (Map.empty, Map.empty)
|
||||||
defaultAssigned = Map.fromList $ map (\a -> (a, ())) $ filter (not . null) internalVariables
|
defaultAssigned = Map.fromList $ map (\a -> (a, ())) $ filter (not . null) internalVariables
|
||||||
|
@ -2176,8 +2186,11 @@ checkUnassignedReferences params t = warnings
|
||||||
return $ " (did you mean '" ++ match ++ "'?)"
|
return $ " (did you mean '" ++ match ++ "'?)"
|
||||||
|
|
||||||
warningFor var place = do
|
warningFor var place = do
|
||||||
|
guard $ isVariableName var
|
||||||
guard . not $ isInArray var place || isGuarded place
|
guard . not $ isInArray var place || isGuarded place
|
||||||
(if isLocal var then warningForLocals else warningForGlobals) var place
|
(if includeGlobals || isLocal var
|
||||||
|
then warningForLocals
|
||||||
|
else warningForGlobals) var place
|
||||||
|
|
||||||
warnings = execWriter . sequence $ mapMaybe (uncurry warningFor) unassigned
|
warnings = execWriter . sequence $ mapMaybe (uncurry warningFor) unassigned
|
||||||
|
|
||||||
|
|
Loading…
Reference in New Issue