Warn about missing space in [ foo= bar ]
This commit is contained in:
parent
af87fe9315
commit
bd9d05c759
|
@ -45,7 +45,7 @@ data Token =
|
||||||
| TC_And Id ConditionType String Token Token
|
| TC_And Id ConditionType String Token Token
|
||||||
| TC_Binary Id ConditionType String Token Token
|
| TC_Binary Id ConditionType String Token Token
|
||||||
| TC_Group Id ConditionType Token
|
| TC_Group Id ConditionType Token
|
||||||
| TC_Noary Id ConditionType Token
|
| TC_Nullary Id ConditionType Token
|
||||||
| TC_Or Id ConditionType String Token Token
|
| TC_Or Id ConditionType String Token Token
|
||||||
| TC_Unary Id ConditionType String Token
|
| TC_Unary Id ConditionType String Token
|
||||||
| T_AND_IF Id
|
| T_AND_IF Id
|
||||||
|
@ -258,7 +258,7 @@ analyze f g i =
|
||||||
delve (TC_Group id typ token) = d1 token $ TC_Group id typ
|
delve (TC_Group id typ token) = d1 token $ TC_Group id typ
|
||||||
delve (TC_Binary id typ op lhs rhs) = d2 lhs rhs $ TC_Binary id typ op
|
delve (TC_Binary id typ op lhs rhs) = d2 lhs rhs $ TC_Binary id typ op
|
||||||
delve (TC_Unary id typ op token) = d1 token $ TC_Unary id typ op
|
delve (TC_Unary id typ op token) = d1 token $ TC_Unary id typ op
|
||||||
delve (TC_Noary id typ token) = d1 token $ TC_Noary id typ
|
delve (TC_Nullary id typ token) = d1 token $ TC_Nullary id typ
|
||||||
|
|
||||||
delve (TA_Binary id op t1 t2) = d2 t1 t2 $ TA_Binary id op
|
delve (TA_Binary id op t1 t2) = d2 t1 t2 $ TA_Binary id op
|
||||||
delve (TA_Assignment id op t1 t2) = d2 t1 t2 $ TA_Assignment id op
|
delve (TA_Assignment id op t1 t2) = d2 t1 t2 $ TA_Assignment id op
|
||||||
|
@ -356,7 +356,7 @@ getId t = case t of
|
||||||
TC_Group id _ _ -> id
|
TC_Group id _ _ -> id
|
||||||
TC_Binary id _ _ _ _ -> id
|
TC_Binary id _ _ _ _ -> id
|
||||||
TC_Unary id _ _ _ -> id
|
TC_Unary id _ _ _ -> id
|
||||||
TC_Noary id _ _ -> id
|
TC_Nullary id _ _ -> id
|
||||||
TA_Binary id _ _ _ -> id
|
TA_Binary id _ _ _ -> id
|
||||||
TA_Assignment id _ _ _ -> id
|
TA_Assignment id _ _ _ -> id
|
||||||
TA_Unary id _ _ -> id
|
TA_Unary id _ _ -> id
|
||||||
|
|
|
@ -171,6 +171,20 @@ getUnquotedLiteral (T_NormalWord _ list) =
|
||||||
str _ = Nothing
|
str _ = Nothing
|
||||||
getUnquotedLiteral _ = Nothing
|
getUnquotedLiteral _ = Nothing
|
||||||
|
|
||||||
|
-- Get the last unquoted T_Literal in a word like "${var}foo"THIS
|
||||||
|
-- or nothing if the word does not end in an unquoted literal.
|
||||||
|
getTrailingUnquotedLiteral :: Token -> Maybe Token
|
||||||
|
getTrailingUnquotedLiteral t =
|
||||||
|
case t of
|
||||||
|
(T_NormalWord _ list@(_:_)) ->
|
||||||
|
from (last list)
|
||||||
|
_ -> Nothing
|
||||||
|
where
|
||||||
|
from t =
|
||||||
|
case t of
|
||||||
|
(T_Literal {}) -> return t
|
||||||
|
_ -> Nothing
|
||||||
|
|
||||||
-- Maybe get the literal string of this token and any globs in it.
|
-- Maybe get the literal string of this token and any globs in it.
|
||||||
getGlobOrLiteralString = getLiteralStringExt f
|
getGlobOrLiteralString = getLiteralStringExt f
|
||||||
where
|
where
|
||||||
|
|
|
@ -98,7 +98,7 @@ nodeChecks = [
|
||||||
,checkSingleBracketOperators
|
,checkSingleBracketOperators
|
||||||
,checkDoubleBracketOperators
|
,checkDoubleBracketOperators
|
||||||
,checkLiteralBreakingTest
|
,checkLiteralBreakingTest
|
||||||
,checkConstantNoary
|
,checkConstantNullary
|
||||||
,checkDivBeforeMult
|
,checkDivBeforeMult
|
||||||
,checkArithmeticDeref
|
,checkArithmeticDeref
|
||||||
,checkArithmeticBadOctal
|
,checkArithmeticBadOctal
|
||||||
|
@ -1021,7 +1021,7 @@ prop_checkLiteralBreakingTest8 = verifyNot checkLiteralBreakingTest "[ $(true)$(
|
||||||
prop_checkLiteralBreakingTest10 = verify checkLiteralBreakingTest "[ -z foo ]"
|
prop_checkLiteralBreakingTest10 = verify checkLiteralBreakingTest "[ -z foo ]"
|
||||||
checkLiteralBreakingTest _ t = potentially $
|
checkLiteralBreakingTest _ t = potentially $
|
||||||
case t of
|
case t of
|
||||||
(TC_Noary _ _ w@(T_NormalWord _ l)) -> do
|
(TC_Nullary _ _ w@(T_NormalWord _ l)) -> do
|
||||||
guard . not $ isConstant w -- Covered by SC2078
|
guard . not $ isConstant w -- Covered by SC2078
|
||||||
comparisonWarning l `mplus` tautologyWarning w "Argument to implicit -n is always true due to literal strings."
|
comparisonWarning l `mplus` tautologyWarning w "Argument to implicit -n is always true due to literal strings."
|
||||||
(TC_Unary _ _ op w@(T_NormalWord _ l)) ->
|
(TC_Unary _ _ op w@(T_NormalWord _ l)) ->
|
||||||
|
@ -1045,14 +1045,14 @@ checkLiteralBreakingTest _ t = potentially $
|
||||||
token <- listToMaybe $ filter isNonEmpty $ getWordParts t
|
token <- listToMaybe $ filter isNonEmpty $ getWordParts t
|
||||||
return $ err (getId token) 2157 s
|
return $ err (getId token) 2157 s
|
||||||
|
|
||||||
prop_checkConstantNoary = verify checkConstantNoary "[[ '$(foo)' ]]"
|
prop_checkConstantNullary = verify checkConstantNullary "[[ '$(foo)' ]]"
|
||||||
prop_checkConstantNoary2 = verify checkConstantNoary "[ \"-f lol\" ]"
|
prop_checkConstantNullary2 = verify checkConstantNullary "[ \"-f lol\" ]"
|
||||||
prop_checkConstantNoary3 = verify checkConstantNoary "[[ cmd ]]"
|
prop_checkConstantNullary3 = verify checkConstantNullary "[[ cmd ]]"
|
||||||
prop_checkConstantNoary4 = verify checkConstantNoary "[[ ! cmd ]]"
|
prop_checkConstantNullary4 = verify checkConstantNullary "[[ ! cmd ]]"
|
||||||
prop_checkConstantNoary5 = verify checkConstantNoary "[[ true ]]"
|
prop_checkConstantNullary5 = verify checkConstantNullary "[[ true ]]"
|
||||||
prop_checkConstantNoary6 = verify checkConstantNoary "[ 1 ]"
|
prop_checkConstantNullary6 = verify checkConstantNullary "[ 1 ]"
|
||||||
prop_checkConstantNoary7 = verify checkConstantNoary "[ false ]"
|
prop_checkConstantNullary7 = verify checkConstantNullary "[ false ]"
|
||||||
checkConstantNoary _ (TC_Noary _ _ t) | isConstant t =
|
checkConstantNullary _ (TC_Nullary _ _ t) | isConstant t =
|
||||||
case fromMaybe "" $ getLiteralString t of
|
case fromMaybe "" $ getLiteralString t of
|
||||||
"false" -> err (getId t) 2158 "[ false ] is true. Remove the brackets."
|
"false" -> err (getId t) 2158 "[ false ] is true. Remove the brackets."
|
||||||
"0" -> err (getId t) 2159 "[ 0 ] is true. Use 'false' instead."
|
"0" -> err (getId t) 2159 "[ 0 ] is true. Use 'false' instead."
|
||||||
|
@ -1062,7 +1062,7 @@ checkConstantNoary _ (TC_Noary _ _ t) | isConstant t =
|
||||||
where
|
where
|
||||||
string = fromMaybe "" $ getLiteralString t
|
string = fromMaybe "" $ getLiteralString t
|
||||||
|
|
||||||
checkConstantNoary _ _ = return ()
|
checkConstantNullary _ _ = return ()
|
||||||
|
|
||||||
prop_checkForDecimals1 = verify checkForDecimals "((3.14*c))"
|
prop_checkForDecimals1 = verify checkForDecimals "((3.14*c))"
|
||||||
prop_checkForDecimals2 = verify checkForDecimals "foo[1.2]=bar"
|
prop_checkForDecimals2 = verify checkForDecimals "foo[1.2]=bar"
|
||||||
|
@ -1180,10 +1180,10 @@ prop_checkValidCondOps2a= verifyNot checkValidCondOps "[ 3 \\> 2 ]"
|
||||||
prop_checkValidCondOps3 = verifyNot checkValidCondOps "[ 1 = 2 -a 3 -ge 4 ]"
|
prop_checkValidCondOps3 = verifyNot checkValidCondOps "[ 1 = 2 -a 3 -ge 4 ]"
|
||||||
prop_checkValidCondOps4 = verifyNot checkValidCondOps "[[ ! -v foo ]]"
|
prop_checkValidCondOps4 = verifyNot checkValidCondOps "[[ ! -v foo ]]"
|
||||||
checkValidCondOps _ (TC_Binary id _ s _ _)
|
checkValidCondOps _ (TC_Binary id _ s _ _)
|
||||||
| s `notElem` ["-nt", "-ot", "-ef", "==", "!=", "<=", ">=", "-eq", "-ne", "-lt", "-le", "-gt", "-ge", "=~", ">", "<", "=", "\\<", "\\>", "\\<=", "\\>="] =
|
| s `notElem` binaryTestOps =
|
||||||
warn id 2057 "Unknown binary operator."
|
warn id 2057 "Unknown binary operator."
|
||||||
checkValidCondOps _ (TC_Unary id _ s _)
|
checkValidCondOps _ (TC_Unary id _ s _)
|
||||||
| s `notElem` [ "!", "-a", "-b", "-c", "-d", "-e", "-f", "-g", "-h", "-L", "-k", "-p", "-r", "-s", "-S", "-t", "-u", "-w", "-x", "-O", "-G", "-N", "-z", "-n", "-o", "-v", "-R"] =
|
| s `notElem` unaryTestOps =
|
||||||
warn id 2058 "Unknown unary operator."
|
warn id 2058 "Unknown unary operator."
|
||||||
checkValidCondOps _ _ = return ()
|
checkValidCondOps _ _ = return ()
|
||||||
|
|
||||||
|
@ -2362,7 +2362,7 @@ prop_checkGrepQ5= verifyNot checkShouldUseGrepQ "rm $(ls | grep file)"
|
||||||
prop_checkGrepQ6= verifyNot checkShouldUseGrepQ "[[ -n $(pgrep foo) ]]"
|
prop_checkGrepQ6= verifyNot checkShouldUseGrepQ "[[ -n $(pgrep foo) ]]"
|
||||||
checkShouldUseGrepQ params t =
|
checkShouldUseGrepQ params t =
|
||||||
potentially $ case t of
|
potentially $ case t of
|
||||||
TC_Noary id _ token -> check id True token
|
TC_Nullary id _ token -> check id True token
|
||||||
TC_Unary id _ "-n" token -> check id True token
|
TC_Unary id _ "-n" token -> check id True token
|
||||||
TC_Unary id _ "-z" token -> check id False token
|
TC_Unary id _ "-z" token -> check id False token
|
||||||
_ -> fail "not check"
|
_ -> fail "not check"
|
||||||
|
|
|
@ -217,7 +217,7 @@ isQuoteFreeNode strict tree t =
|
||||||
-- Are any subnodes inherently self-quoting?
|
-- Are any subnodes inherently self-quoting?
|
||||||
isQuoteFreeContext t =
|
isQuoteFreeContext t =
|
||||||
case t of
|
case t of
|
||||||
TC_Noary _ DoubleBracket _ -> return True
|
TC_Nullary _ DoubleBracket _ -> return True
|
||||||
TC_Unary _ DoubleBracket _ _ -> return True
|
TC_Unary _ DoubleBracket _ _ -> return True
|
||||||
TC_Binary _ DoubleBracket _ _ _ -> return True
|
TC_Binary _ DoubleBracket _ _ _ -> return True
|
||||||
TA_Sequence {} -> return True
|
TA_Sequence {} -> return True
|
||||||
|
|
|
@ -85,6 +85,17 @@ sampleWords = [
|
||||||
"zulu"
|
"zulu"
|
||||||
]
|
]
|
||||||
|
|
||||||
|
binaryTestOps = [
|
||||||
|
"-nt", "-ot", "-ef", "==", "!=", "<=", ">=", "-eq", "-ne", "-lt", "-le",
|
||||||
|
"-gt", "-ge", "=~", ">", "<", "=", "\\<", "\\>", "\\<=", "\\>="
|
||||||
|
]
|
||||||
|
|
||||||
|
unaryTestOps = [
|
||||||
|
"!", "-a", "-b", "-c", "-d", "-e", "-f", "-g", "-h", "-L", "-k", "-p",
|
||||||
|
"-r", "-s", "-S", "-t", "-u", "-w", "-x", "-O", "-G", "-N", "-z", "-n",
|
||||||
|
"-o", "-v", "-R"
|
||||||
|
]
|
||||||
|
|
||||||
shellForExecutable :: String -> Maybe Shell
|
shellForExecutable :: String -> Maybe Shell
|
||||||
shellForExecutable name =
|
shellForExecutable name =
|
||||||
case name of
|
case name of
|
||||||
|
|
|
@ -333,6 +333,13 @@ parseProblemAtWithEnd start end level code msg = do
|
||||||
|
|
||||||
parseProblemAt pos = parseProblemAtWithEnd pos pos
|
parseProblemAt pos = parseProblemAtWithEnd pos pos
|
||||||
|
|
||||||
|
parseProblemAtId :: Monad m => Id -> Severity -> Integer -> String -> SCParser m ()
|
||||||
|
parseProblemAtId id level code msg = do
|
||||||
|
map <- getMap
|
||||||
|
let pos = Map.findWithDefault
|
||||||
|
(error "Internal error (no position for id). Please report.") id map
|
||||||
|
parseProblemAt pos level code msg
|
||||||
|
|
||||||
-- Store non-parse problems inside
|
-- Store non-parse problems inside
|
||||||
|
|
||||||
parseNote c l a = do
|
parseNote c l a = do
|
||||||
|
@ -528,7 +535,7 @@ readConditionContents single =
|
||||||
condSpacing requiresSpacing
|
condSpacing requiresSpacing
|
||||||
return x
|
return x
|
||||||
|
|
||||||
readCondNoaryOrBinary = do
|
readCondNullaryOrBinary = do
|
||||||
id <- getNextId
|
id <- getNextId
|
||||||
x <- readCondWord `attempting` (do
|
x <- readCondWord `attempting` (do
|
||||||
pos <- getPosition
|
pos <- getPosition
|
||||||
|
@ -545,7 +552,16 @@ readConditionContents single =
|
||||||
then readRegex
|
then readRegex
|
||||||
else readCondWord <|> (parseProblemAt pos ErrorC 1027 "Expected another argument for this operator." >> mzero)
|
else readCondWord <|> (parseProblemAt pos ErrorC 1027 "Expected another argument for this operator." >> mzero)
|
||||||
return (x `op` y)
|
return (x `op` y)
|
||||||
) <|> return (TC_Noary id typ x)
|
) <|> ( do
|
||||||
|
checkTrailingOp x
|
||||||
|
return $ TC_Nullary id typ x
|
||||||
|
)
|
||||||
|
|
||||||
|
checkTrailingOp x = fromMaybe (return ()) $ do
|
||||||
|
(T_Literal id str) <- getTrailingUnquotedLiteral x
|
||||||
|
trailingOp <- listToMaybe (filter (`isSuffixOf` str) binaryTestOps)
|
||||||
|
return $ parseProblemAtId id ErrorC 1108 $
|
||||||
|
"You need a space before and after the " ++ trailingOp ++ " ."
|
||||||
|
|
||||||
readCondGroup = do
|
readCondGroup = do
|
||||||
id <- getNextId
|
id <- getNextId
|
||||||
|
@ -622,7 +638,7 @@ readConditionContents single =
|
||||||
return $ TC_Unary id typ "!" expr
|
return $ TC_Unary id typ "!" expr
|
||||||
|
|
||||||
readCondExpr =
|
readCondExpr =
|
||||||
readCondGroup <|> readCondUnaryExp <|> readCondNoaryOrBinary
|
readCondGroup <|> readCondUnaryExp <|> readCondNullaryOrBinary
|
||||||
|
|
||||||
readCondOr = chainl1 readCondAnd readCondAndOp
|
readCondOr = chainl1 readCondAnd readCondAndOp
|
||||||
readCondAnd = chainl1 readCondTerm readCondOrOp
|
readCondAnd = chainl1 readCondTerm readCondOrOp
|
||||||
|
|
Loading…
Reference in New Issue