Warn about (( 1 -lt 2 ))
This commit is contained in:
parent
6c1abb2dee
commit
e3bef9dc97
|
@ -649,6 +649,7 @@ prop_a19= isOk readArithmeticContents "\\\n3 +\\\n 2"
|
||||||
prop_a20= isOk readArithmeticContents "a ? b ? c : d : e"
|
prop_a20= isOk readArithmeticContents "a ? b ? c : d : e"
|
||||||
prop_a21= isOk readArithmeticContents "a ? b : c ? d : e"
|
prop_a21= isOk readArithmeticContents "a ? b : c ? d : e"
|
||||||
prop_a22= isOk readArithmeticContents "!!a"
|
prop_a22= isOk readArithmeticContents "!!a"
|
||||||
|
readArithmeticContents :: Monad m => SCParser m Token
|
||||||
readArithmeticContents =
|
readArithmeticContents =
|
||||||
readSequence
|
readSequence
|
||||||
where
|
where
|
||||||
|
@ -662,12 +663,40 @@ readArithmeticContents =
|
||||||
id <- getNextId
|
id <- getNextId
|
||||||
op <- choice (map (\x -> try $ do
|
op <- choice (map (\x -> try $ do
|
||||||
s <- string x
|
s <- string x
|
||||||
notFollowedBy2 $ oneOf "&|<>="
|
failIfIncompleteOp
|
||||||
return s
|
return s
|
||||||
) op)
|
) op)
|
||||||
spacing
|
spacing
|
||||||
return $ token id op
|
return $ token id op
|
||||||
|
|
||||||
|
failIfIncompleteOp = notFollowedBy2 $ oneOf "&|<>="
|
||||||
|
|
||||||
|
-- Read binary minus, but also check for -lt, -gt and friends:
|
||||||
|
readMinusOp = do
|
||||||
|
id <- getNextId
|
||||||
|
pos <- getPosition
|
||||||
|
try $ do
|
||||||
|
char '-'
|
||||||
|
failIfIncompleteOp
|
||||||
|
optional $ do
|
||||||
|
(str, alt) <- lookAhead . choice $ map tryOp [
|
||||||
|
("lt", "<"),
|
||||||
|
("gt", ">"),
|
||||||
|
("le", "<="),
|
||||||
|
("ge", ">="),
|
||||||
|
("eq", "=="),
|
||||||
|
("ne", "!=")
|
||||||
|
]
|
||||||
|
parseProblemAt pos ErrorC 1106 $ "In arithmetic contexts, use " ++ alt ++ " instead of -" ++ str
|
||||||
|
spacing
|
||||||
|
return $ TA_Binary id "-"
|
||||||
|
where
|
||||||
|
tryOp (str, alt) = try $ do
|
||||||
|
string str
|
||||||
|
spacing1
|
||||||
|
return (str, alt)
|
||||||
|
|
||||||
|
|
||||||
readArrayIndex = do
|
readArrayIndex = do
|
||||||
id <- getNextId
|
id <- getNextId
|
||||||
char '['
|
char '['
|
||||||
|
@ -737,7 +766,7 @@ readArithmeticContents =
|
||||||
readEquated = readCompared `splitBy` ["==", "!="]
|
readEquated = readCompared `splitBy` ["==", "!="]
|
||||||
readCompared = readShift `splitBy` ["<=", ">=", "<", ">"]
|
readCompared = readShift `splitBy` ["<=", ">=", "<", ">"]
|
||||||
readShift = readAddition `splitBy` ["<<", ">>"]
|
readShift = readAddition `splitBy` ["<<", ">>"]
|
||||||
readAddition = readMultiplication `splitBy` ["+", "-"]
|
readAddition = chainl1 readMultiplication (readBinary ["+"] <|> readMinusOp)
|
||||||
readMultiplication = readExponential `splitBy` ["*", "/", "%"]
|
readMultiplication = readExponential `splitBy` ["*", "/", "%"]
|
||||||
readExponential = readAnyNegated `splitBy` ["**"]
|
readExponential = readAnyNegated `splitBy` ["**"]
|
||||||
|
|
||||||
|
@ -1336,7 +1365,7 @@ readDollarExpression = do
|
||||||
arithmetic <|> readDollarExpansion <|> readDollarBracket <|> readDollarBraceCommandExpansion <|> readDollarBraced <|> readDollarVariable
|
arithmetic <|> readDollarExpansion <|> readDollarBracket <|> readDollarBraceCommandExpansion <|> readDollarBraced <|> readDollarVariable
|
||||||
where
|
where
|
||||||
arithmetic = readAmbiguous "$((" readDollarArithmetic readDollarExpansion (\pos ->
|
arithmetic = readAmbiguous "$((" readDollarArithmetic readDollarExpansion (\pos ->
|
||||||
parseNoteAt pos WarningC 1102 "Shells disambiguate $(( differently or not at all. If the first $( should start command substitution, add a space after it.")
|
parseNoteAt pos WarningC 1102 "Shells disambiguate $(( differently or not at all. For $(command substition), add space after $( . For $((arithmetics)), fix parsing errors.")
|
||||||
|
|
||||||
prop_readDollarSingleQuote = isOk readDollarSingleQuote "$'foo\\\'lol'"
|
prop_readDollarSingleQuote = isOk readDollarSingleQuote "$'foo\\\'lol'"
|
||||||
readDollarSingleQuote = called "$'..' expression" $ do
|
readDollarSingleQuote = called "$'..' expression" $ do
|
||||||
|
@ -1389,7 +1418,7 @@ readAmbiguous prefix expected alternative warner = do
|
||||||
try . lookAhead $ string prefix
|
try . lookAhead $ string prefix
|
||||||
-- If the expected parser fails, try the alt.
|
-- If the expected parser fails, try the alt.
|
||||||
-- If the alt fails, run the expected one again for the errors.
|
-- If the alt fails, run the expected one again for the errors.
|
||||||
try (forgetOnFailure expected) <|> try (withAlt pos) <|> expected
|
try expected <|> try (withAlt pos) <|> expected
|
||||||
where
|
where
|
||||||
withAlt pos = do
|
withAlt pos = do
|
||||||
t <- forgetOnFailure alternative
|
t <- forgetOnFailure alternative
|
||||||
|
@ -2205,8 +2234,7 @@ readCompoundCommand = do
|
||||||
cmd <- choice [
|
cmd <- choice [
|
||||||
readBraceGroup,
|
readBraceGroup,
|
||||||
readAmbiguous "((" readArithmeticExpression readSubshell (\pos ->
|
readAmbiguous "((" readArithmeticExpression readSubshell (\pos ->
|
||||||
parseNoteAt pos WarningC 1105 "Shells disambiguate (( differently or not at all. If the first ( should start a subshell, add a space after it."),
|
parseNoteAt pos WarningC 1105 "Shells disambiguate (( differently or not at all. For subshell, add spaces around ( . For ((, fix parsing errors."),
|
||||||
--readArithmeticExpression,
|
|
||||||
readSubshell,
|
readSubshell,
|
||||||
readCondition,
|
readCondition,
|
||||||
readWhileClause,
|
readWhileClause,
|
||||||
|
|
Loading…
Reference in New Issue