mirror of
				https://github.com/koalaman/shellcheck.git
				synced 2025-11-04 18:28:23 +08:00 
			
		
		
		
	Parse empty [ ] conditionals
This commit is contained in:
		@@ -48,6 +48,7 @@ data Token =
 | 
			
		||||
    | TC_Nullary Id ConditionType Token
 | 
			
		||||
    | TC_Or Id ConditionType String Token Token
 | 
			
		||||
    | TC_Unary Id ConditionType String Token
 | 
			
		||||
    | TC_Empty Id ConditionType
 | 
			
		||||
    | T_AND_IF Id
 | 
			
		||||
    | T_AndIf Id Token Token
 | 
			
		||||
    | T_Arithmetic Id Token
 | 
			
		||||
@@ -372,6 +373,7 @@ getId t = case t of
 | 
			
		||||
        T_CoProcBody id _ -> id
 | 
			
		||||
        T_Include id _ _ -> id
 | 
			
		||||
        T_UnparsedIndex id _ _ -> id
 | 
			
		||||
        TC_Empty id _ -> id
 | 
			
		||||
 | 
			
		||||
blank :: Monad m => Token -> m ()
 | 
			
		||||
blank = const $ return ()
 | 
			
		||||
 
 | 
			
		||||
@@ -163,6 +163,7 @@ nodeChecks = [
 | 
			
		||||
    ,checkSplittingInArrays
 | 
			
		||||
    ,checkRedirectionToNumber
 | 
			
		||||
    ,checkGlobAsCommand
 | 
			
		||||
    ,checkEmptyCondition
 | 
			
		||||
    ]
 | 
			
		||||
 | 
			
		||||
 | 
			
		||||
@@ -2819,5 +2820,11 @@ checkGlobAsCommand _ t = case t of
 | 
			
		||||
            warn (getId first) 2211 "This is a glob used as a command name. Was it supposed to be in ${..}, array, or is it missing quoting?"
 | 
			
		||||
    _ -> return ()
 | 
			
		||||
 | 
			
		||||
prop_checkEmptyCondition1 = verify checkEmptyCondition "if [ ]; then ..; fi"
 | 
			
		||||
prop_checkEmptyCondition2 = verifyNot checkEmptyCondition "[ foo -o bar ]"
 | 
			
		||||
checkEmptyCondition _ t = case t of
 | 
			
		||||
    TC_Empty id _ -> style id 2212 "Use 'false' instead of empty [/[[ conditionals."
 | 
			
		||||
    _ -> return ()
 | 
			
		||||
 | 
			
		||||
return []
 | 
			
		||||
runTests =  $( [| $(forAllProperties) (quickCheckWithResult (stdArgs { maxSuccess = 1 }) ) |])
 | 
			
		||||
 
 | 
			
		||||
@@ -848,11 +848,13 @@ prop_readCondition14= isOk readCondition "[ foo '>' bar ]"
 | 
			
		||||
prop_readCondition15= isOk readCondition "[ foo \">=\" bar ]"
 | 
			
		||||
prop_readCondition16= isOk readCondition "[ foo \\< bar ]"
 | 
			
		||||
prop_readCondition17= isOk readCondition "[[ ${file::1} = [-.\\|/\\\\] ]]"
 | 
			
		||||
prop_readCondition18= isOk readCondition "[ ]"
 | 
			
		||||
readCondition = called "test expression" $ do
 | 
			
		||||
    opos <- getPosition
 | 
			
		||||
    id <- getNextId
 | 
			
		||||
    open <- try (string "[[") <|> string "["
 | 
			
		||||
    let single = open == "["
 | 
			
		||||
    let typ = if single then SingleBracket else DoubleBracket
 | 
			
		||||
 | 
			
		||||
    pos <- getPosition
 | 
			
		||||
    space <- allspacing
 | 
			
		||||
@@ -864,7 +866,11 @@ readCondition = called "test expression" $ do
 | 
			
		||||
    when (single && '\n' `elem` space) $
 | 
			
		||||
        parseProblemAt pos ErrorC 1080 "You need \\ before line feeds to break lines in [ ]."
 | 
			
		||||
 | 
			
		||||
    condition <- readConditionContents single
 | 
			
		||||
    condition <- readConditionContents single <|> do
 | 
			
		||||
        guard . not . null $ space
 | 
			
		||||
        lookAhead $ string "]"
 | 
			
		||||
        id <- getNextIdAt pos
 | 
			
		||||
        return $ TC_Empty id typ
 | 
			
		||||
 | 
			
		||||
    cpos <- getPosition
 | 
			
		||||
    close <- try (string "]]") <|> string "]" <|> fail "Expected test to end here (don't wrap commands in []/[[]])"
 | 
			
		||||
@@ -872,7 +878,7 @@ readCondition = called "test expression" $ do
 | 
			
		||||
    when (open == "[" && close /= "]" ) $ parseProblemAt opos ErrorC 1034 "Did you mean [[ ?"
 | 
			
		||||
    spacing
 | 
			
		||||
    many readCmdWord -- Read and throw away remainders to get then/do warnings. Fixme?
 | 
			
		||||
    return $ T_Condition id (if single then SingleBracket else DoubleBracket) condition
 | 
			
		||||
    return $ T_Condition id typ condition
 | 
			
		||||
 | 
			
		||||
readAnnotationPrefix = do
 | 
			
		||||
    char '#'
 | 
			
		||||
 
 | 
			
		||||
		Reference in New Issue
	
	Block a user