Track whether braces were present in T_DollarBraced

References of the form $var and ${var} both map to the same structure in
the AST, which prevents any later analysis functions from distinguishing
them.  In preparation for adding checks that need this info, add a Bool
to T_DollarBraced that tracks whether the braces were seen at parsing
time and update all references so that this change is a no-op.
This commit is contained in:
Benjamin Gordon 2019-04-29 14:26:39 -06:00 committed by Benjamin Gordon
parent 0358090b3c
commit aa3b709b5d
7 changed files with 33 additions and 34 deletions

View file

@ -754,7 +754,7 @@ checkShorthandIf _ _ = return ()
prop_checkDollarStar = verify checkDollarStar "for f in $*; do ..; done"
prop_checkDollarStar2 = verifyNot checkDollarStar "a=$*"
prop_checkDollarStar3 = verifyNot checkDollarStar "[[ $* = 'a b' ]]"
checkDollarStar p t@(T_NormalWord _ [b@(T_DollarBraced id _)])
checkDollarStar p t@(T_NormalWord _ [b@(T_DollarBraced id _ _)])
| bracedString b == "*" =
unless (isStrictlyQuoteFree (parentMap p) t) $
warn id 2048 "Use \"$@\" (with quotes) to prevent whitespace problems."
@ -825,7 +825,7 @@ checkArrayWithoutIndex params _ =
doVariableFlowAnalysis readF writeF defaultMap (variableFlow params)
where
defaultMap = Map.fromList $ map (\x -> (x,())) arrayVariables
readF _ (T_DollarBraced id token) _ = do
readF _ (T_DollarBraced id _ token) _ = do
map <- get
return . maybeToList $ do
name <- getLiteralString token
@ -1267,7 +1267,7 @@ prop_checkArithmeticDeref12= verify checkArithmeticDeref "for ((i=0; $i < 3; i))
prop_checkArithmeticDeref13= verifyNot checkArithmeticDeref "(( $$ ))"
prop_checkArithmeticDeref14= verifyNot checkArithmeticDeref "(( $! ))"
prop_checkArithmeticDeref15= verifyNot checkArithmeticDeref "(( ${!var} ))"
checkArithmeticDeref params t@(TA_Expansion _ [b@(T_DollarBraced id _)]) =
checkArithmeticDeref params t@(TA_Expansion _ [b@(T_DollarBraced id _ _)]) =
unless (isException $ bracedString b) getWarning
where
isException [] = True
@ -1302,8 +1302,7 @@ prop_checkComparisonAgainstGlob3 = verify checkComparisonAgainstGlob "[ $cow = *
prop_checkComparisonAgainstGlob4 = verifyNot checkComparisonAgainstGlob "[ $cow = foo ]"
prop_checkComparisonAgainstGlob5 = verify checkComparisonAgainstGlob "[[ $cow != $bar ]]"
prop_checkComparisonAgainstGlob6 = verify checkComparisonAgainstGlob "[ $f != /* ]"
checkComparisonAgainstGlob _ (TC_Binary _ DoubleBracket op _ (T_NormalWord id [T_DollarBraced _ _]))
checkComparisonAgainstGlob _ (TC_Binary _ DoubleBracket op _ (T_NormalWord id [T_DollarBraced _ _ _]))
| op `elem` ["=", "==", "!="] =
warn id 2053 $ "Quote the right-hand side of " ++ op ++ " in [[ ]] to prevent glob matching."
checkComparisonAgainstGlob params (TC_Binary _ SingleBracket op _ word)
@ -1457,7 +1456,7 @@ prop_checkIndirectExpansion2 = verifyNot checkIndirectExpansion "${foo//$n/lol}"
prop_checkIndirectExpansion3 = verify checkIndirectExpansion "${$#}"
prop_checkIndirectExpansion4 = verify checkIndirectExpansion "${var${n}_$((i%2))}"
prop_checkIndirectExpansion5 = verifyNot checkIndirectExpansion "${bar}"
checkIndirectExpansion _ (T_DollarBraced i (T_NormalWord _ contents)) =
checkIndirectExpansion _ (T_DollarBraced i _ (T_NormalWord _ contents)) =
when (isIndirection contents) $
err i 2082 "To expand via indirection, use arrays, ${!name} or (for sh only) eval."
where
@ -1467,7 +1466,7 @@ checkIndirectExpansion _ (T_DollarBraced i (T_NormalWord _ contents)) =
isIndirectionPart t =
case t of T_DollarExpansion _ _ -> Just True
T_Backticked _ _ -> Just True
T_DollarBraced _ _ -> Just True
T_DollarBraced _ _ _ -> Just True
T_DollarArithmetic _ _ -> Just True
T_Literal _ s -> if all isVariableChar s
then Nothing
@ -1494,7 +1493,7 @@ checkInexplicablyUnquoted params (T_NormalWord id tokens) = mapM_ check (tails t
check (T_DoubleQuoted _ a:trapped:T_DoubleQuoted _ b:_) =
case trapped of
T_DollarExpansion id _ -> warnAboutExpansion id
T_DollarBraced id _ -> warnAboutExpansion id
T_DollarBraced id _ _ -> warnAboutExpansion id
T_Literal id s ->
unless (quotesSingleThing a && quotesSingleThing b || isRegex (getPath (parentMap params) trapped)) $
warnAboutLiteral id
@ -1515,7 +1514,7 @@ checkInexplicablyUnquoted params (T_NormalWord id tokens) = mapM_ check (tails t
-- the quotes were probably intentional and harmless.
quotesSingleThing x = case x of
[T_DollarExpansion _ _] -> True
[T_DollarBraced _ _] -> True
[T_DollarBraced _ _ _] -> True
[T_Backticked _ _] -> True
_ -> False
@ -1822,7 +1821,7 @@ checkSpacefulness' onFind params t =
isExpansion t =
case t of
(T_DollarBraced _ _ ) -> True
(T_DollarBraced _ _ _ ) -> True
_ -> False
isSpacefulWord :: (String -> Bool) -> [Token] -> Bool
@ -1836,7 +1835,7 @@ checkSpacefulness' onFind params t =
T_Extglob {} -> True
T_Literal _ s -> s `containsAny` globspace
T_SingleQuoted _ s -> s `containsAny` globspace
T_DollarBraced _ _ -> spacefulF $ getBracedReference $ bracedString x
T_DollarBraced _ _ _ -> spacefulF $ getBracedReference $ bracedString x
T_NormalWord _ w -> isSpacefulWord spacefulF w
T_DoubleQuoted _ w -> isSpacefulWord spacefulF w
_ -> False
@ -1874,7 +1873,7 @@ checkQuotesInLiterals params t =
return []
writeF _ _ _ _ = return []
forToken map (T_DollarBraced id t) =
forToken map (T_DollarBraced id _ t) =
-- skip getBracedReference here to avoid false positives on PE
Map.lookup (concat . oversimplify $ t) map
forToken quoteMap (T_DoubleQuoted id tokens) =
@ -1888,7 +1887,7 @@ checkQuotesInLiterals params t =
squashesQuotes t =
case t of
T_DollarBraced id _ -> "#" `isPrefixOf` bracedString t
T_DollarBraced id _ _ -> "#" `isPrefixOf` bracedString t
_ -> False
readF _ expr name = do
@ -2135,10 +2134,10 @@ checkUnassignedReferences params t = warnings
isInArray var t = any isArray $ getPath (parentMap params) t
where
isArray T_Array {} = True
isArray b@(T_DollarBraced _ _) | var /= getBracedReference (bracedString b) = True
isArray b@(T_DollarBraced _ _ _) | var /= getBracedReference (bracedString b) = True
isArray _ = False
isGuarded (T_DollarBraced _ v) =
isGuarded (T_DollarBraced _ _ v) =
rest `matches` guardRegex
where
name = concat $ oversimplify v
@ -2224,7 +2223,7 @@ checkWhileReadPitfalls _ _ = return ()
prop_checkPrefixAssign1 = verify checkPrefixAssignmentReference "var=foo echo $var"
prop_checkPrefixAssign2 = verifyNot checkPrefixAssignmentReference "var=$(echo $var) cmd"
checkPrefixAssignmentReference params t@(T_DollarBraced id value) =
checkPrefixAssignmentReference params t@(T_DollarBraced id _ value) =
check path
where
name = getBracedReference $ bracedString t
@ -3026,7 +3025,7 @@ checkSplittingInArrays params t =
T_DollarExpansion id _ -> forCommand id
T_DollarBraceCommandExpansion id _ -> forCommand id
T_Backticked id _ -> forCommand id
T_DollarBraced id str |
T_DollarBraced id _ str |
not (isCountingReference part)
&& not (isQuotedAlternativeReference part)
&& not (getBracedReference (bracedString part) `elem` variablesWithoutSpaces)