Warn about literal, unquoted {/}
This commit is contained in:
parent
e6d81ca7b7
commit
680f838c63
|
@ -705,6 +705,8 @@ prop_readNormalWord = isOk readNormalWord "'foo'\"bar\"{1..3}baz$(lol)"
|
||||||
prop_readNormalWord2 = isOk readNormalWord "foo**(foo)!!!(@@(bar))"
|
prop_readNormalWord2 = isOk readNormalWord "foo**(foo)!!!(@@(bar))"
|
||||||
prop_readNormalWord3 = isOk readNormalWord "foo#"
|
prop_readNormalWord3 = isOk readNormalWord "foo#"
|
||||||
prop_readNormalWord4 = isOk readNormalWord "$\"foo\"$'foo\nbar'"
|
prop_readNormalWord4 = isOk readNormalWord "$\"foo\"$'foo\nbar'"
|
||||||
|
prop_readNormalWord5 = isWarning readNormalWord "${foo}}"
|
||||||
|
prop_readNormalWord6 = isOk readNormalWord "foo/{}"
|
||||||
readNormalWord = readNormalishWord ""
|
readNormalWord = readNormalishWord ""
|
||||||
|
|
||||||
readNormalishWord end = do
|
readNormalishWord end = do
|
||||||
|
@ -715,14 +717,24 @@ readNormalishWord end = do
|
||||||
return $ T_NormalWord id x
|
return $ T_NormalWord id x
|
||||||
|
|
||||||
checkPossibleTermination pos [T_Literal _ x] =
|
checkPossibleTermination pos [T_Literal _ x] =
|
||||||
if x `elem` ["do", "done", "then", "fi", "esac", "}"]
|
if x `elem` ["do", "done", "then", "fi", "esac"]
|
||||||
then parseProblemAt pos WarningC 1010 $ "Use semicolon or linefeed before '" ++ x ++ "' (or quote to make it literal)."
|
then parseProblemAt pos WarningC 1010 $ "Use semicolon or linefeed before '" ++ x ++ "' (or quote to make it literal)."
|
||||||
else return ()
|
else return ()
|
||||||
checkPossibleTermination _ _ = return ()
|
checkPossibleTermination _ _ = return ()
|
||||||
|
|
||||||
readNormalWordPart end = do
|
readNormalWordPart end = do
|
||||||
checkForParenthesis
|
checkForParenthesis
|
||||||
readSingleQuoted <|> readDoubleQuoted <|> readGlob <|> readNormalDollar <|> readBraced <|> readBackTicked <|> readProcSub <|> (readNormalLiteral end)
|
choice [
|
||||||
|
readSingleQuoted,
|
||||||
|
readDoubleQuoted,
|
||||||
|
readGlob,
|
||||||
|
readNormalDollar,
|
||||||
|
readBraced,
|
||||||
|
readBackTicked,
|
||||||
|
readProcSub,
|
||||||
|
readNormalLiteral end,
|
||||||
|
readLiteralCurlyBraces
|
||||||
|
]
|
||||||
where
|
where
|
||||||
checkForParenthesis = do
|
checkForParenthesis = do
|
||||||
return () `attempting` do
|
return () `attempting` do
|
||||||
|
@ -730,6 +742,19 @@ readNormalWordPart end = do
|
||||||
lookAhead $ char '('
|
lookAhead $ char '('
|
||||||
parseProblemAt pos ErrorC 1036 "'(' is invalid here. Did you forget to escape it?"
|
parseProblemAt pos ErrorC 1036 "'(' is invalid here. Did you forget to escape it?"
|
||||||
|
|
||||||
|
readLiteralCurlyBraces = do
|
||||||
|
id <- getNextId
|
||||||
|
str <- findParam <|> literalBraces
|
||||||
|
return $ T_Literal id str
|
||||||
|
|
||||||
|
findParam = try $ string "{}"
|
||||||
|
literalBraces = do
|
||||||
|
pos <- getPosition
|
||||||
|
c <- oneOf "{}"
|
||||||
|
parseProblemAt pos WarningC 1083 $
|
||||||
|
"This " ++ [c] ++ " is literal. Check expression (missing ;/\\n?) or quote it."
|
||||||
|
return [c]
|
||||||
|
|
||||||
|
|
||||||
readSpacePart = do
|
readSpacePart = do
|
||||||
id <- getNextId
|
id <- getNextId
|
||||||
|
@ -928,7 +953,7 @@ readGlob = readExtglob <|> readSimple <|> readClass <|> readGlobbyLiteral
|
||||||
return $ T_Literal id [c]
|
return $ T_Literal id [c]
|
||||||
|
|
||||||
readNormalLiteralPart end = do
|
readNormalLiteralPart end = do
|
||||||
readNormalEscaped <|> (many1 $ noneOf (end ++ quotableChars ++ extglobStartChars ++ "["))
|
readNormalEscaped <|> (many1 $ noneOf (end ++ quotableChars ++ extglobStartChars ++ "[{}"))
|
||||||
|
|
||||||
readNormalEscaped = called "escaped char" $ do
|
readNormalEscaped = called "escaped char" $ do
|
||||||
pos <- getPosition
|
pos <- getPosition
|
||||||
|
@ -1033,7 +1058,10 @@ readBraced = try $ do
|
||||||
char '{'
|
char '{'
|
||||||
str <- many1 ((readDoubleQuotedLiteral >>= (strip)) <|> readGenericLiteral1 (oneOf "}\"" <|> whitespace))
|
str <- many1 ((readDoubleQuotedLiteral >>= (strip)) <|> readGenericLiteral1 (oneOf "}\"" <|> whitespace))
|
||||||
char '}'
|
char '}'
|
||||||
return $ T_BraceExpansion id $ concat str
|
let result = concat str
|
||||||
|
unless (',' `elem` result || ".." `isInfixOf` result) $
|
||||||
|
fail "Not a brace expression"
|
||||||
|
return $ T_BraceExpansion id $ result
|
||||||
|
|
||||||
readNormalDollar = readDollarExpression <|> readDollarDoubleQuote <|> readDollarSingleQuote <|> readDollarLonely
|
readNormalDollar = readDollarExpression <|> readDollarDoubleQuote <|> readDollarSingleQuote <|> readDollarLonely
|
||||||
readDoubleQuotedDollar = readDollarExpression <|> readDollarLonely
|
readDoubleQuotedDollar = readDollarExpression <|> readDollarLonely
|
||||||
|
@ -1083,7 +1111,7 @@ readArithmeticExpression = called "((..)) command" $ do
|
||||||
|
|
||||||
prop_readDollarBraced1 = isOk readDollarBraced "${foo//bar/baz}"
|
prop_readDollarBraced1 = isOk readDollarBraced "${foo//bar/baz}"
|
||||||
prop_readDollarBraced2 = isOk readDollarBraced "${foo/'{cow}'}"
|
prop_readDollarBraced2 = isOk readDollarBraced "${foo/'{cow}'}"
|
||||||
prop_readDollarBraced3 = isOk readDollarBraced "${foo%%$(echo cow})}"
|
prop_readDollarBraced3 = isOk readDollarBraced "${foo%%$(echo cow\\})}"
|
||||||
prop_readDollarBraced4 = isOk readDollarBraced "${foo#\\}}"
|
prop_readDollarBraced4 = isOk readDollarBraced "${foo#\\}}"
|
||||||
readDollarBraced = called "parameter expansion" $ do
|
readDollarBraced = called "parameter expansion" $ do
|
||||||
id <- getNextId
|
id <- getNextId
|
||||||
|
|
Loading…
Reference in New Issue