Allow [ foo \> bar ], while warning for [[ .. \> .. ]] and [ 1 \< 2 ]

This commit is contained in:
Vidar Holen 2013-05-14 15:59:58 -07:00
parent 10d4abf235
commit 92d0ae8b6b
2 changed files with 18 additions and 6 deletions

View File

@ -54,6 +54,7 @@ basicChecks = [
,checkUnquotedN ,checkUnquotedN
,checkNumberComparisons ,checkNumberComparisons
,checkSingleBracketOperators ,checkSingleBracketOperators
,checkDoubleBracketOperators
,checkNoaryWasBinary ,checkNoaryWasBinary
,checkConstantNoary ,checkConstantNoary
,checkBraceExpansionVars ,checkBraceExpansionVars
@ -486,7 +487,7 @@ prop_checkNumberComparisons4 = verify checkNumberComparisons "[[ $foo > 2.72 ]]"
prop_checkNumberComparisons5 = verify checkNumberComparisons "[[ $foo -le 2.72 ]]" prop_checkNumberComparisons5 = verify checkNumberComparisons "[[ $foo -le 2.72 ]]"
prop_checkNumberComparisons6 = verify checkNumberComparisons "[[ 3.14 = $foo ]]" prop_checkNumberComparisons6 = verify checkNumberComparisons "[[ 3.14 = $foo ]]"
checkNumberComparisons (TC_Binary id typ op lhs rhs) = do checkNumberComparisons (TC_Binary id typ op lhs rhs) = do
when (op `elem` ["<", ">", "<=", ">="]) $ do when (op `elem` ["<", ">", "<=", ">=", "\\<", "\\>", "\\<=", "\\>="]) $ do
when (isNum lhs || isNum rhs) $ err id $ "\"" ++ op ++ "\" is for string comparisons. Use " ++ (eqv op) ++" ." when (isNum lhs || isNum rhs) $ err id $ "\"" ++ op ++ "\" is for string comparisons. Use " ++ (eqv op) ++" ."
mapM_ checkDecimals [lhs, rhs] mapM_ checkDecimals [lhs, rhs]
@ -500,6 +501,7 @@ checkNumberComparisons (TC_Binary id typ op lhs rhs) = do
_ -> False _ -> False
isFraction t = case deadSimple t of [v] -> isJust $ matchRegex floatRegex v isFraction t = case deadSimple t of [v] -> isJust $ matchRegex floatRegex v
_ -> False _ -> False
eqv ('\\':s) = eqv s
eqv "<" = "-lt" eqv "<" = "-lt"
eqv ">" = "-gt" eqv ">" = "-gt"
eqv "<=" = "-le" eqv "<=" = "-le"
@ -513,11 +515,20 @@ prop_checkSingleBracketOperators2 = verify checkSingleBracketOperators "[ $foo >
prop_checkSingleBracketOperators3 = verifyNot checkSingleBracketOperators "[[ foo < bar ]]" prop_checkSingleBracketOperators3 = verifyNot checkSingleBracketOperators "[[ foo < bar ]]"
prop_checkSingleBracketOperators5 = verify checkSingleBracketOperators "until [ $n <= $z ]; do echo foo; done" prop_checkSingleBracketOperators5 = verify checkSingleBracketOperators "until [ $n <= $z ]; do echo foo; done"
checkSingleBracketOperators (TC_Binary id typ op lhs rhs) checkSingleBracketOperators (TC_Binary id typ op lhs rhs)
| typ == SingleBracket && op `elem` ["<", ">", "<=", ">=", "=~"] = | typ == SingleBracket && op `elem` ["<", ">", "<=", ">="] =
err id $ "Can't use " ++ op ++" in [ ]. Use [[ ]]." err id $ "Can't use " ++ op ++" in [ ]. Escape it or use [[..]]."
checkSingleBracketOperators (TC_Binary id typ op lhs rhs)
| typ == SingleBracket && op == "=~" =
err id $ "Can't use " ++ op ++" in [ ]. Use [[..]] instead."
checkSingleBracketOperators _ = return () checkSingleBracketOperators _ = return ()
prop_checkDoubleBracketOperators1 = verify checkDoubleBracketOperators "[[ 3 \\< 4 ]]"
prop_checkDoubleBracketOperators3 = verifyNot checkDoubleBracketOperators "[[ foo < bar ]]"
checkDoubleBracketOperators x@(TC_Binary id typ op lhs rhs)
| typ == DoubleBracket && op `elem` ["\\<", "\\>", "\\<=", "\\>="] =
err id $ "Escaping " ++ op ++" is required in [..], but invalid in [[..]]"
checkDoubleBracketOperators _ = return ()
prop_checkQuotedCondRegex1 = verify checkQuotedCondRegex "[[ $foo =~ \"bar\" ]]" prop_checkQuotedCondRegex1 = verify checkQuotedCondRegex "[[ $foo =~ \"bar\" ]]"
prop_checkQuotedCondRegex2 = verify checkQuotedCondRegex "[[ $foo =~ 'cow' ]]" prop_checkQuotedCondRegex2 = verify checkQuotedCondRegex "[[ $foo =~ 'cow' ]]"
prop_checkQuotedCondRegex3 = verifyNot checkQuotedCondRegex "[[ $foo =~ $foo ]]" prop_checkQuotedCondRegex3 = verifyNot checkQuotedCondRegex "[[ $foo =~ $foo ]]"
@ -649,10 +660,11 @@ allModifiedVariables t = snd $ runState (doAnalysis (\x -> modify $ (++) (getMod
prop_checkValidCondOps1 = verify checkValidCondOps "[[ a -xz b ]]" prop_checkValidCondOps1 = verify checkValidCondOps "[[ a -xz b ]]"
prop_checkValidCondOps2 = verify checkValidCondOps "[ -M a ]" prop_checkValidCondOps2 = verify checkValidCondOps "[ -M a ]"
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 _ _)
| not (s `elem` ["-nt", "-ot", "-ef", "==", "!=", "<=", ">=", "-eq", "-ne", "-lt", "-le", "-gt", "-ge", "=~", ">", "<", "="]) = | not (s `elem` ["-nt", "-ot", "-ef", "==", "!=", "<=", ">=", "-eq", "-ne", "-lt", "-le", "-gt", "-ge", "=~", ">", "<", "=", "\\<", "\\>", "\\<=", "\\>="]) =
warn id "Unknown binary operator." warn id "Unknown binary operator."
checkValidCondOps (TC_Unary id _ s _) checkValidCondOps (TC_Unary id _ s _)
| not (s `elem` [ "!", "-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"]) = | not (s `elem` [ "!", "-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"]) =

View File

@ -213,7 +213,7 @@ readConditionContents single = do
typ = if single then SingleBracket else DoubleBracket typ = if single then SingleBracket else DoubleBracket
readCondBinaryOp = try $ do readCondBinaryOp = try $ do
id <- getNextId id <- getNextId
op <- (choice $ (map tryOp ["==", "!=", "<=", ">=", "=~", ">", "<", "="])) <|> otherOp op <- (choice $ (map tryOp ["==", "!=", "<=", ">=", "=~", ">", "<", "=", "\\<=", "\\>=", "\\<", "\\>"])) <|> otherOp
hardCondSpacing hardCondSpacing
return op return op
where where