From 0897ab70924ca75ad7b9a78d09d9708ee9fa099f Mon Sep 17 00:00:00 2001 From: MortimerMcMire315 Date: Mon, 28 Nov 2016 16:06:02 -0500 Subject: [PATCH] Add handling for special characters in parameter substitutions. Fixes koalaman/shellcheck#562. Special characters inside braces are parsed into T_ParamSubSpecialChar instead of T_Literal so that they are not flagged in the function checkInexplicablyUnquoted when sandwiched between double quotes. --- ShellCheck/AST.hs | 2 ++ ShellCheck/Analytics.hs | 3 ++- ShellCheck/Parser.hs | 10 +++++++++- 3 files changed, 13 insertions(+), 2 deletions(-) diff --git a/ShellCheck/AST.hs b/ShellCheck/AST.hs index 28dffc8..39dfff2 100644 --- a/ShellCheck/AST.hs +++ b/ShellCheck/AST.hs @@ -111,6 +111,7 @@ data Token = | T_NormalWord Id [Token] | T_OR_IF Id | T_OrIf Id (Token) (Token) + | T_ParamSubSpecialChar Id -- e.g. '%' in ${foo%bar} or '/' in ${foo/bar/baz} | T_Pipeline Id [Token] [Token] -- [Pipe separators] [Commands] | T_ProcSub Id String [Token] | T_Rbrace Id @@ -319,6 +320,7 @@ getId t = case t of T_DollarBraced id _ -> id T_DollarArithmetic id _ -> id T_BraceExpansion id _ -> id + T_ParamSubSpecialChar id -> id T_DollarBraceCommandExpansion id _ -> id T_IoFile id _ _ -> id T_IoDuplicate id _ _ -> id diff --git a/ShellCheck/Analytics.hs b/ShellCheck/Analytics.hs index c44e91f..9585c04 100644 --- a/ShellCheck/Analytics.hs +++ b/ShellCheck/Analytics.hs @@ -1324,6 +1324,7 @@ prop_checkInexplicablyUnquoted3 = verifyNot checkInexplicablyUnquoted "wget --us prop_checkInexplicablyUnquoted4 = verify checkInexplicablyUnquoted "echo \"VALUES (\"id\")\"" prop_checkInexplicablyUnquoted5 = verifyNot checkInexplicablyUnquoted "\"$dir\"/\"$file\"" prop_checkInexplicablyUnquoted6 = verifyNot checkInexplicablyUnquoted "\"$dir\"some_stuff\"$file\"" +prop_checkInexplicablyUnquoted7 = verifyNot checkInexplicablyUnquoted "${dir/\"foo\"/\"bar\"}" checkInexplicablyUnquoted _ (T_NormalWord id tokens) = mapM_ check (tails tokens) where check (T_SingleQuoted _ _:T_Literal id str:_) @@ -1352,7 +1353,7 @@ checkInexplicablyUnquoted _ (T_NormalWord id tokens) = mapM_ check (tails tokens warnAboutExpansion id = warn id 2027 "The surrounding quotes actually unquote this. Remove or escape them." warnAboutLiteral id = - warn id 2140 "Word is on the form \"A\"B\"C\" (B indicated). Did you mean \"ABC\" or \"A\\\"B\\\"C\"?" + warn id 2140 "Word is of the form \"A\"B\"C\" (B indicated). Did you mean \"ABC\" or \"A\\\"B\\\"C\"?" checkInexplicablyUnquoted _ _ = return () prop_checkTildeInQuotes1 = verify checkTildeInQuotes "var=\"~/out.txt\"" diff --git a/ShellCheck/Parser.hs b/ShellCheck/Parser.hs index a1837ab..d04c87d 100644 --- a/ShellCheck/Parser.hs +++ b/ShellCheck/Parser.hs @@ -64,6 +64,7 @@ variableStart = upper <|> lower <|> oneOf "_" variableChars = upper <|> lower <|> digit <|> oneOf "_" functionChars = variableChars <|> oneOf ":+-.?" specialVariable = oneOf "@*#?-$!" +paramSubSpecialChars = oneOf "/:+-=%" quotableChars = "|&;<>()\\ '\t\n\r\xA0" ++ doubleQuotableChars quotable = almostSpace <|> unicodeDoubleQuote <|> oneOf quotableChars bracedQuotable = oneOf "}\"$`'" @@ -1003,13 +1004,20 @@ readDollarBracedWord = do list <- many readDollarBracedPart return $ T_NormalWord id list -readDollarBracedPart = readSingleQuoted <|> readDoubleQuoted <|> readExtglob <|> readNormalDollar <|> readUnquotedBackTicked <|> readDollarBracedLiteral +readDollarBracedPart = readSingleQuoted <|> readDoubleQuoted <|> + readParamSubSpecialChar <|> readExtglob <|> readNormalDollar <|> + readUnquotedBackTicked <|> readDollarBracedLiteral readDollarBracedLiteral = do id <- getNextId vars <- (readBraceEscaped <|> (anyChar >>= \x -> return [x])) `reluctantlyTill1` bracedQuotable return $ T_Literal id $ concat vars +readParamSubSpecialChar = do + id <- getNextId + many1 paramSubSpecialChars + return $ T_ParamSubSpecialChar id + prop_readProcSub1 = isOk readProcSub "<(echo test | wc -l)" prop_readProcSub2 = isOk readProcSub "<( if true; then true; fi )" prop_readProcSub3 = isOk readProcSub "<( # nothing here \n)"