Stop using generic char 'c' in 2022
This commit is contained in:
parent
d8878ed852
commit
c26c2b8536
|
@ -226,6 +226,8 @@ prop_isVariableName3 = not $ isVariableName "test: "
|
||||||
isVariableName (x:r) = isVariableStartChar x && all isVariableChar r
|
isVariableName (x:r) = isVariableStartChar x && all isVariableChar r
|
||||||
isVariableName _ = False
|
isVariableName _ = False
|
||||||
|
|
||||||
|
potentially = fromMaybe (return ())
|
||||||
|
|
||||||
matchAll re = unfoldr f
|
matchAll re = unfoldr f
|
||||||
where
|
where
|
||||||
f str = do
|
f str = do
|
||||||
|
@ -254,9 +256,17 @@ isConfusedGlobRegex ('*':_) = True
|
||||||
isConfusedGlobRegex [x,'*'] | x /= '\\' = True
|
isConfusedGlobRegex [x,'*'] | x /= '\\' = True
|
||||||
isConfusedGlobRegex _ = False
|
isConfusedGlobRegex _ = False
|
||||||
|
|
||||||
isPotentiallyConfusedGlobRegex =
|
getSuspiciousRegexWildcard str =
|
||||||
let re = mkRegex "[a-z1-9]\\*" in
|
if (not $ str `matches` contra)
|
||||||
isJust . matchRegex re
|
then do
|
||||||
|
match <- matchRegex suspicious str
|
||||||
|
str <- match !!! 0
|
||||||
|
str !!! 0
|
||||||
|
else
|
||||||
|
fail "looks good"
|
||||||
|
where
|
||||||
|
suspicious = mkRegex "([A-Za-z1-9])\\*"
|
||||||
|
contra = mkRegex "[^a-zA-Z1-9]\\*|[][^$+\\\\]"
|
||||||
|
|
||||||
matches string regex = isJust $ matchRegex regex string
|
matches string regex = isJust $ matchRegex regex string
|
||||||
|
|
||||||
|
@ -1395,6 +1405,7 @@ prop_checkGrepRe6 = verifyNot checkGrepRe "grep foo \\*.mp3"
|
||||||
prop_checkGrepRe7 = verify checkGrepRe "grep *foo* file"
|
prop_checkGrepRe7 = verify checkGrepRe "grep *foo* file"
|
||||||
prop_checkGrepRe8 = verify checkGrepRe "ls | grep foo*.jpg"
|
prop_checkGrepRe8 = verify checkGrepRe "ls | grep foo*.jpg"
|
||||||
prop_checkGrepRe9 = verifyNot checkGrepRe "grep '[0-9]*' file"
|
prop_checkGrepRe9 = verifyNot checkGrepRe "grep '[0-9]*' file"
|
||||||
|
prop_checkGrepRe10= verifyNot checkGrepRe "grep '^aa*' file"
|
||||||
|
|
||||||
checkGrepRe _ = checkCommand "grep" (const f) where
|
checkGrepRe _ = checkCommand "grep" (const f) where
|
||||||
-- --regex=*(extglob) doesn't work. Fixme?
|
-- --regex=*(extglob) doesn't work. Fixme?
|
||||||
|
@ -1408,11 +1419,16 @@ checkGrepRe _ = checkCommand "grep" (const f) where
|
||||||
let string = concat $ deadSimple re
|
let string = concat $ deadSimple re
|
||||||
if isConfusedGlobRegex string then
|
if isConfusedGlobRegex string then
|
||||||
warn (getId re) 2063 $ "Grep uses regex, but this looks like a glob."
|
warn (getId re) 2063 $ "Grep uses regex, but this looks like a glob."
|
||||||
else
|
else potentially $ do
|
||||||
if (isPotentiallyConfusedGlobRegex string)
|
char <- getSuspiciousRegexWildcard string
|
||||||
then info (getId re) 2022 "Note that c* does not mean \"c followed by anything\" in regex."
|
return $ info (getId re) 2022 $
|
||||||
else return ()
|
"Note that unlike globs, " ++ [char] ++ "* here matches '" ++ [char, char, char] ++ "' but not '" ++ (wordStartingWith char) ++ "'."
|
||||||
|
|
||||||
|
wordStartingWith c =
|
||||||
|
head . filter ([c] `isPrefixOf`) $ candidates
|
||||||
|
where
|
||||||
|
candidates =
|
||||||
|
sampleWords ++ (map (\(x:r) -> (toUpper x) : r) sampleWords) ++ [c:"test"]
|
||||||
|
|
||||||
prop_checkTrapQuotes1 = verify checkTrapQuotes "trap \"echo $num\" INT"
|
prop_checkTrapQuotes1 = verify checkTrapQuotes "trap \"echo $num\" INT"
|
||||||
prop_checkTrapQuotes1a= verify checkTrapQuotes "trap \"echo `ls`\" INT"
|
prop_checkTrapQuotes1a= verify checkTrapQuotes "trap \"echo `ls`\" INT"
|
||||||
|
|
|
@ -74,3 +74,11 @@ commonCommands = [
|
||||||
"val", "vi", "wait", "wc", "what", "who", "write", "xargs", "yacc",
|
"val", "vi", "wait", "wc", "what", "who", "write", "xargs", "yacc",
|
||||||
"zcat"
|
"zcat"
|
||||||
]
|
]
|
||||||
|
|
||||||
|
sampleWords = [
|
||||||
|
"alpha", "bravo", "charlie", "delta", "echo", "foxtrot",
|
||||||
|
"golf", "hotel", "india", "juliett", "kilo", "lima", "mike",
|
||||||
|
"november", "oscar", "papa", "quebec", "romeo", "sierra",
|
||||||
|
"tango", "uniform", "victor", "whiskey", "xray", "yankee",
|
||||||
|
"zulu"
|
||||||
|
]
|
||||||
|
|
Loading…
Reference in New Issue