diff --git a/src/ShellCheck/ASTLib.hs b/src/ShellCheck/ASTLib.hs index da91d09..4fdf078 100644 --- a/src/ShellCheck/ASTLib.hs +++ b/src/ShellCheck/ASTLib.hs @@ -134,13 +134,9 @@ isUnquotedFlag token = fromMaybe False $ do str <- getLeadingUnquotedString token return $ "-" `isPrefixOf` str --- Given a T_DollarBraced, return a simplified version of the string contents. -bracedString (T_DollarBraced _ _ l) = concat $ oversimplify l -bracedString _ = error "Internal shellcheck error, please report! (bracedString on non-variable)" - -- Is this an expansion of multiple items of an array? -isArrayExpansion t@(T_DollarBraced _ _ _) = - let string = bracedString t in +isArrayExpansion (T_DollarBraced _ _ l) = + let string = concat $ oversimplify l in "@" `isPrefixOf` string || not ("#" `isPrefixOf` string) && "[@]" `isInfixOf` string isArrayExpansion _ = False @@ -148,8 +144,8 @@ isArrayExpansion _ = False -- Is it possible that this arg becomes multiple args? mayBecomeMultipleArgs t = willBecomeMultipleArgs t || f t where - f t@(T_DollarBraced _ _ _) = - let string = bracedString t in + f (T_DollarBraced _ _ l) = + let string = concat $ oversimplify l in "!" `isPrefixOf` string f (T_DoubleQuoted _ parts) = any f parts f (T_NormalWord _ parts) = any f parts diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index 599e257..125835a 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -781,8 +781,8 @@ 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 _ _)]) - | bracedString b == "*" && +checkDollarStar p t@(T_NormalWord _ [T_DollarBraced id _ l]) + | concat (oversimplify l) == "*" && not (isStrictlyQuoteFree (parentMap p) t) = warn id 2048 "Use \"$@\" (with quotes) to prevent whitespace problems." checkDollarStar _ _ = return () @@ -1309,8 +1309,8 @@ prop_checkArithmeticDeref13= verifyNot checkArithmeticDeref "(( $$ ))" prop_checkArithmeticDeref14= verifyNot checkArithmeticDeref "(( $! ))" prop_checkArithmeticDeref15= verifyNot checkArithmeticDeref "(( ${!var} ))" prop_checkArithmeticDeref16= verifyNot checkArithmeticDeref "(( ${x+1} + ${x=42} ))" -checkArithmeticDeref params t@(TA_Expansion _ [b@(T_DollarBraced id _ _)]) = - unless (isException $ bracedString b) getWarning +checkArithmeticDeref params t@(TA_Expansion _ [T_DollarBraced id _ l]) = + unless (isException $ concat $ oversimplify l) getWarning where isException [] = True isException s@(h:_) = any (`elem` "/.:#%?*@$-!+=^,") s || isDigit h @@ -1869,6 +1869,10 @@ checkSpacefulness params = checkSpacefulness' onFind params any (`isPrefixOf` modifier) ["=", ":="] && isParamTo parents ":" token + -- Given a T_DollarBraced, return a simplified version of the string contents. + bracedString (T_DollarBraced _ _ l) = concat $ oversimplify l + bracedString _ = error "Internal shellcheck error, please report! (bracedString on non-variable)" + prop_checkSpacefulness4v= verifyTree checkVerboseSpacefulness "foo=3; foo=$(echo $foo)" prop_checkSpacefulness8v= verifyTree checkVerboseSpacefulness "a=foo\\ bar; a=foo; rm $a" prop_checkSpacefulness28v = verifyTree checkVerboseSpacefulness "exec {n}>&1; echo $n" @@ -1940,7 +1944,7 @@ checkSpacefulness' onFind params t = T_DollarArithmetic _ _ -> SpaceNone T_Literal _ s -> fromLiteral s T_SingleQuoted _ s -> fromLiteral s - T_DollarBraced _ _ _ -> spacefulF $ getBracedReference $ bracedString x + T_DollarBraced _ _ l -> spacefulF $ getBracedReference $ concat $ oversimplify l T_NormalWord _ w -> isSpacefulWord spacefulF w T_DoubleQuoted _ w -> isSpacefulWord spacefulF w _ -> SpaceEmpty @@ -1955,19 +1959,16 @@ prop_CheckVariableBraces1 = verify checkVariableBraces "a='123'; echo $a" prop_CheckVariableBraces2 = verifyNot checkVariableBraces "a='123'; echo ${a}" prop_CheckVariableBraces3 = verifyNot checkVariableBraces "#shellcheck disable=SC2016\necho '$a'" prop_CheckVariableBraces4 = verifyNot checkVariableBraces "echo $* $1" -checkVariableBraces params t = - case t of - T_DollarBraced id False _ - | name `notElem` unbracedVariables -> - styleWithFix id 2250 - "Prefer putting braces around variable references even when not strictly required." - (fixFor t) - - _ -> return () +checkVariableBraces params t@(T_DollarBraced id False l) + | name `notElem` unbracedVariables = + styleWithFix id 2250 + "Prefer putting braces around variable references even when not strictly required." + (fixFor t) where - name = getBracedReference $ bracedString t + name = getBracedReference $ concat $ oversimplify l fixFor token = fixWith [replaceStart (getId token) params 1 "${" ,replaceEnd (getId token) params 0 "}"] +checkVariableBraces _ _ = return () prop_checkQuotesInLiterals1 = verifyTree checkQuotesInLiterals "param='--foo=\"bar\"'; app $param" prop_checkQuotesInLiterals1a= verifyTree checkQuotesInLiterals "param=\"--foo='lolbar'\"; app $param" @@ -2013,7 +2014,7 @@ checkQuotesInLiterals params t = squashesQuotes t = case t of - T_DollarBraced id _ _ -> "#" `isPrefixOf` bracedString t + T_DollarBraced id _ l -> "#" `isPrefixOf` concat (oversimplify l) _ -> False readF _ expr name = do @@ -2274,7 +2275,7 @@ checkUnassignedReferences' includeGlobals 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 (T_DollarBraced _ _ l) | var /= getBracedReference (concat $ oversimplify l) = True isArray _ = False isGuarded (T_DollarBraced _ _ v) = @@ -2402,7 +2403,7 @@ prop_checkPrefixAssign2 = verifyNot checkPrefixAssignmentReference "var=$(echo $ checkPrefixAssignmentReference params t@(T_DollarBraced id _ value) = check path where - name = getBracedReference $ bracedString t + name = getBracedReference $ concat $ oversimplify value path = getPath (parentMap params) t idPath = map getId path @@ -3035,7 +3036,7 @@ checkReturnAgainstZero _ token = isZero t = getLiteralString t == Just "0" isExitCode t = case getWordParts t of - [exp@T_DollarBraced {}] -> bracedString exp == "?" + [T_DollarBraced _ _ l] -> concat (oversimplify l) == "?" _ -> False message id = style id 2181 "Check exit code directly with e.g. 'if mycmd;', not indirectly with $?." @@ -3220,7 +3221,7 @@ checkSplittingInArrays params t = T_DollarBraced id _ str | not (isCountingReference part) && not (isQuotedAlternativeReference part) - && getBracedReference (bracedString part) `notElem` variablesWithoutSpaces + && getBracedReference (concat $ oversimplify str) `notElem` variablesWithoutSpaces -> warn id 2206 $ if shellType params == Ksh then "Quote to prevent word splitting/globbing, or split robustly with read -A or while read." diff --git a/src/ShellCheck/AnalyzerLib.hs b/src/ShellCheck/AnalyzerLib.hs index 3a7f7da..69ebfe6 100644 --- a/src/ShellCheck/AnalyzerLib.hs +++ b/src/ShellCheck/AnalyzerLib.hs @@ -498,7 +498,7 @@ getModifiedVariables t = return (t, token, str, DataString SourceChecked) T_DollarBraced _ _ l -> do - let string = bracedString t + let string = concat $ oversimplify l let modifier = getBracedModifier string guard $ any (`isPrefixOf` modifier) ["=", ":="] return (t, t, getBracedReference string, DataString $ SourceFrom [l]) @@ -703,7 +703,7 @@ getOffsetReferences mods = fromMaybe [] $ do getReferencedVariables parents t = case t of - T_DollarBraced id _ l -> let str = bracedString t in + T_DollarBraced id _ l -> let str = concat $ oversimplify l in (t, t, getBracedReference str) : map (\x -> (l, l, x)) ( getIndexReferences str @@ -895,8 +895,8 @@ isCountingReference _ = False -- FIXME: doesn't handle ${a:+$var} vs ${a:+"$var"} isQuotedAlternativeReference t = case t of - T_DollarBraced _ _ _ -> - getBracedModifier (bracedString t) `matches` re + T_DollarBraced _ _ l -> + getBracedModifier (concat $ oversimplify l) `matches` re _ -> False where re = mkRegex "(^|\\]):?\\+" diff --git a/src/ShellCheck/Checks/Commands.hs b/src/ShellCheck/Checks/Commands.hs index c68bdd1..99acd5f 100644 --- a/src/ShellCheck/Checks/Commands.hs +++ b/src/ShellCheck/Checks/Commands.hs @@ -680,8 +680,7 @@ prop_checkExportedExpansions4 = verifyNot checkExportedExpansions "export ${foo? checkExportedExpansions = CommandCheck (Exactly "export") (mapM_ check . arguments) where check t = sequence_ $ do - var <- getSingleUnmodifiedVariable t - let name = bracedString var + name <- getSingleUnmodifiedBracedString t return . warn (getId t) 2163 $ "This does not export '" ++ name ++ "'. Remove $/${} for that, or use ${var?} to quiet." @@ -702,21 +701,20 @@ checkReadExpansions = CommandCheck (Exactly "read") check check cmd = mapM_ warning $ getVars cmd warning t = sequence_ $ do - var <- getSingleUnmodifiedVariable t - let name = bracedString var + name <- getSingleUnmodifiedBracedString t guard $ isVariableName name -- e.g. not $1 return . warn (getId t) 2229 $ "This does not read '" ++ name ++ "'. Remove $/${} for that, or use ${var?} to quiet." -- Return the single variable expansion that makes up this word, if any. -- e.g. $foo -> $foo, "$foo"'' -> $foo , "hello $name" -> Nothing -getSingleUnmodifiedVariable :: Token -> Maybe Token -getSingleUnmodifiedVariable word = +getSingleUnmodifiedBracedString :: Token -> Maybe String +getSingleUnmodifiedBracedString word = case getWordParts word of - [t@(T_DollarBraced {})] -> - let contents = bracedString t + [T_DollarBraced _ _ l] -> + let contents = concat $ oversimplify l name = getBracedReference contents - in guard (contents == name) >> return t + in guard (contents == name) >> return contents _ -> Nothing prop_checkAliasesUsesArgs1 = verify checkAliasesUsesArgs "alias a='cp $1 /a'" diff --git a/src/ShellCheck/Checks/ShellSupport.hs b/src/ShellCheck/Checks/ShellSupport.hs index 49d3212..d9deff6 100644 --- a/src/ShellCheck/Checks/ShellSupport.hs +++ b/src/ShellCheck/Checks/ShellSupport.hs @@ -243,7 +243,7 @@ checkBashisms = ForShell [Sh, Dash] $ \t -> do when (isBashVariable var) $ warnMsg id $ var ++ " is" where - str = bracedString t + str = concat $ oversimplify token var = getBracedReference str check (regex, feature) = when (isJust $ matchRegex regex str) $ warnMsg id feature @@ -506,13 +506,13 @@ checkMultiDimensionalArrays = ForShell [Bash] f case token of T_Assignment _ _ name (first:second:_) _ -> about second T_IndexedElement _ (first:second:_) _ -> about second - T_DollarBraced {} -> - when (isMultiDim token) $ about token + T_DollarBraced _ _ l -> + when (isMultiDim l) $ about token _ -> return () about t = warn (getId t) 2180 "Bash does not support multidimensional arrays. Use 1D or associative arrays." re = mkRegex "^\\[.*\\]\\[.*\\]" -- Fixme, this matches ${foo:- [][]} and such as well - isMultiDim t = getBracedModifier (bracedString t) `matches` re + isMultiDim l = getBracedModifier (concat $ oversimplify l) `matches` re prop_checkPS11 = verify checkPS1Assignments "PS1='\\033[1;35m\\$ '" prop_checkPS11a= verify checkPS1Assignments "export PS1='\\033[1;35m\\$ '"