summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorVidar Holen <spam@vidarholen.net>2018-10-21 14:58:28 -0700
committerVidar Holen <spam@vidarholen.net>2018-10-21 15:25:35 -0700
commitb81524250698ccb0119d055417e22af446665c09 (patch)
tree7f9166ac1684fbba2ff536a2cfe732f6ea3eb214
parent07b5aa2971e4214e972a843fb35b134968e87405 (diff)
Improve regex parsing (fixes #1367)
-rw-r--r--src/ShellCheck/Analytics.hs7
-rw-r--r--src/ShellCheck/Parser.hs21
2 files changed, 19 insertions, 9 deletions
diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs
index 23ea1e0..713a298 100644
--- a/src/ShellCheck/Analytics.hs
+++ b/src/ShellCheck/Analytics.hs
@@ -1037,13 +1037,16 @@ checkQuotedCondRegex _ _ = return ()
prop_checkGlobbedRegex1 = verify checkGlobbedRegex "[[ $foo =~ *foo* ]]"
prop_checkGlobbedRegex2 = verify checkGlobbedRegex "[[ $foo =~ f* ]]"
-prop_checkGlobbedRegex2a = verify checkGlobbedRegex "[[ $foo =~ \\#* ]]"
prop_checkGlobbedRegex3 = verifyNot checkGlobbedRegex "[[ $foo =~ $foo ]]"
prop_checkGlobbedRegex4 = verifyNot checkGlobbedRegex "[[ $foo =~ ^c.* ]]"
+prop_checkGlobbedRegex5 = verifyNot checkGlobbedRegex "[[ $foo =~ \\* ]]"
+prop_checkGlobbedRegex6 = verifyNot checkGlobbedRegex "[[ $foo =~ (o*) ]]"
+prop_checkGlobbedRegex7 = verifyNot checkGlobbedRegex "[[ $foo =~ \\*foo ]]"
+prop_checkGlobbedRegex8 = verifyNot checkGlobbedRegex "[[ $foo =~ x\\* ]]"
checkGlobbedRegex _ (TC_Binary _ DoubleBracket "=~" _ rhs) =
let s = concat $ oversimplify rhs in
when (isConfusedGlobRegex s) $
- warn (getId rhs) 2049 "=~ is for regex. Use == for globs."
+ warn (getId rhs) 2049 "=~ is for regex, but this looks like a glob. Use = instead."
checkGlobbedRegex _ _ = return ()
diff --git a/src/ShellCheck/Parser.hs b/src/ShellCheck/Parser.hs
index 667eaca..aa99379 100644
--- a/src/ShellCheck/Parser.hs
+++ b/src/ShellCheck/Parser.hs
@@ -625,8 +625,8 @@ readConditionContents single =
readSingleQuoted,
readDoubleQuoted,
readDollarExpression,
- readNormalLiteral "( ",
- readPipeLiteral,
+ readLiteralForParser $ readNormalLiteral "( ",
+ readLiteralString "|",
readGlobLiteral
]
readGlobLiteral = do
@@ -636,19 +636,19 @@ readConditionContents single =
return $ T_Literal id [s]
readGroup = called "regex grouping" $ do
start <- startSpan
- char '('
+ p1 <- readLiteralString "("
parts <- many (readPart <|> readRegexLiteral)
- char ')'
+ p2 <- readLiteralString ")"
id <- endSpan start
- return $ T_NormalWord id parts
+ return $ T_NormalWord id (p1:(parts ++ [p2]))
readRegexLiteral = do
start <- startSpan
str <- readGenericLiteral1 (singleQuote <|> doubleQuotable <|> oneOf "()")
id <- endSpan start
return $ T_Literal id str
- readPipeLiteral = do
+ readLiteralString s = do
start <- startSpan
- str <- string "|"
+ str <- string s
id <- endSpan start
return $ T_Literal id str
@@ -2654,6 +2654,13 @@ readStringForParser parser = do
where
readUntil endPos = anyChar `reluctantlyTill` (getPosition >>= guard . (== endPos))
+-- Like readStringForParser, returning the span as a T_Literal
+readLiteralForParser parser = do
+ start <- startSpan
+ str <- readStringForParser parser
+ id <- endSpan start
+ return $ T_Literal id str
+
prop_readAssignmentWord = isOk readAssignmentWord "a=42"
prop_readAssignmentWord2 = isOk readAssignmentWord "b=(1 2 3)"
prop_readAssignmentWord3 = isWarning readAssignmentWord "$b = 13"