mirror of
				https://github.com/koalaman/shellcheck.git
				synced 2025-11-04 09:26:10 +08:00 
			
		
		
		
	Parse let arguments as arithmetic expressions.
This commit is contained in:
		@@ -1195,12 +1195,20 @@ prop_checkArithmeticDeref4 = verifyNot checkArithmeticDeref "(( ! $? ))"
 | 
				
			|||||||
prop_checkArithmeticDeref5 = verifyNot checkArithmeticDeref "(($1))"
 | 
					prop_checkArithmeticDeref5 = verifyNot checkArithmeticDeref "(($1))"
 | 
				
			||||||
prop_checkArithmeticDeref6 = verify checkArithmeticDeref "(( a[$i] ))"
 | 
					prop_checkArithmeticDeref6 = verify checkArithmeticDeref "(( a[$i] ))"
 | 
				
			||||||
prop_checkArithmeticDeref7 = verifyNot checkArithmeticDeref "(( 10#$n ))"
 | 
					prop_checkArithmeticDeref7 = verifyNot checkArithmeticDeref "(( 10#$n ))"
 | 
				
			||||||
 | 
					prop_checkArithmeticDeref8 = verifyNot checkArithmeticDeref "let i=$i+1"
 | 
				
			||||||
checkArithmeticDeref params t@(TA_Expansion _ [T_DollarBraced id l]) =
 | 
					checkArithmeticDeref params t@(TA_Expansion _ [T_DollarBraced id l]) =
 | 
				
			||||||
    unless (excepting $ bracedString l) $
 | 
					    unless ((isException $ bracedString l) || (not isNormal)) $
 | 
				
			||||||
        style id 2004 "$ on variables in (( )) is unnecessary."
 | 
					        style id 2004 "$ on variables in (( )) is unnecessary."
 | 
				
			||||||
  where
 | 
					  where
 | 
				
			||||||
    excepting [] = True
 | 
					    isException [] = True
 | 
				
			||||||
    excepting s = any (`elem` "/.:#%?*@") s || isDigit (head s)
 | 
					    isException s = any (`elem` "/.:#%?*@") s || isDigit (head s)
 | 
				
			||||||
 | 
					    isNormal = fromMaybe True $ msum $ map isNormalContext $ (parents params t)
 | 
				
			||||||
 | 
					    isNormalContext t =
 | 
				
			||||||
 | 
					        case t of
 | 
				
			||||||
 | 
					            T_Arithmetic {} -> return True
 | 
				
			||||||
 | 
					            T_DollarArithmetic {} -> return True
 | 
				
			||||||
 | 
					            T_SimpleCommand {} -> return False
 | 
				
			||||||
 | 
					            _ -> fail "Irrelevant"
 | 
				
			||||||
checkArithmeticDeref _ _ = return ()
 | 
					checkArithmeticDeref _ _ = return ()
 | 
				
			||||||
 | 
					
 | 
				
			||||||
prop_checkArithmeticBadOctal1 = verify checkArithmeticBadOctal "(( 0192 ))"
 | 
					prop_checkArithmeticBadOctal1 = verify checkArithmeticBadOctal "(( 0192 ))"
 | 
				
			||||||
@@ -2265,6 +2273,7 @@ prop_checkUnused15= verifyNotTree checkUnusedAssignments "x=(1); n=0; (( x[n] ))
 | 
				
			|||||||
prop_checkUnused16= verifyNotTree checkUnusedAssignments "foo=5; declare -x foo"
 | 
					prop_checkUnused16= verifyNotTree checkUnusedAssignments "foo=5; declare -x foo"
 | 
				
			||||||
prop_checkUnused17= verifyNotTree checkUnusedAssignments "read -i 'foo' -e -p 'Input: ' bar; $bar;"
 | 
					prop_checkUnused17= verifyNotTree checkUnusedAssignments "read -i 'foo' -e -p 'Input: ' bar; $bar;"
 | 
				
			||||||
prop_checkUnused18= verifyNotTree checkUnusedAssignments "a=1; arr=( [$a]=42 ); echo \"${arr[@]}\""
 | 
					prop_checkUnused18= verifyNotTree checkUnusedAssignments "a=1; arr=( [$a]=42 ); echo \"${arr[@]}\""
 | 
				
			||||||
 | 
					prop_checkUnused19= verifyNotTree checkUnusedAssignments "a=1; let b=a+1; echo $b"
 | 
				
			||||||
checkUnusedAssignments params t = snd $ runWriter (mapM_ checkAssignment flow)
 | 
					checkUnusedAssignments params t = snd $ runWriter (mapM_ checkAssignment flow)
 | 
				
			||||||
  where
 | 
					  where
 | 
				
			||||||
    flow = variableFlow params
 | 
					    flow = variableFlow params
 | 
				
			||||||
 
 | 
				
			|||||||
@@ -1345,20 +1345,20 @@ readSimpleCommand = called "simple command" $ do
 | 
				
			|||||||
    case cmd of
 | 
					    case cmd of
 | 
				
			||||||
      Nothing -> return $ makeSimpleCommand id1 id2 prefix [] []
 | 
					      Nothing -> return $ makeSimpleCommand id1 id2 prefix [] []
 | 
				
			||||||
      Just cmd -> do
 | 
					      Just cmd -> do
 | 
				
			||||||
            suffix <- option [] $
 | 
					            suffix <- option [] $ getParser readCmdSuffix cmd [
 | 
				
			||||||
                        if isModifierCommand cmd
 | 
					                        (["declare", "export", "local", "readonly", "typeset"], readModifierSuffix),
 | 
				
			||||||
                        then readModifierSuffix
 | 
					                        (["time"], readTimeSuffix),
 | 
				
			||||||
                        else if isTimeCommand cmd
 | 
					                        (["let"], readLetSuffix)
 | 
				
			||||||
                             then readTimeSuffix
 | 
					                    ]
 | 
				
			||||||
                             else readCmdSuffix
 | 
					 | 
				
			||||||
            return $ makeSimpleCommand id1 id2 prefix [cmd] suffix
 | 
					            return $ makeSimpleCommand id1 id2 prefix [cmd] suffix
 | 
				
			||||||
  where
 | 
					  where
 | 
				
			||||||
    isModifierCommand (T_NormalWord _ [T_Literal _ s]) =
 | 
					    isCommand strings (T_NormalWord _ [T_Literal _ s]) = s `elem` strings
 | 
				
			||||||
        s `elem` ["declare", "export", "local", "readonly", "typeset"]
 | 
					    isCommand _ _ = False
 | 
				
			||||||
    isModifierCommand _ = False
 | 
					    getParser def cmd [] = def
 | 
				
			||||||
    -- Might not belong in T_SimpleCommand. Fixme?
 | 
					    getParser def cmd ((list, action):rest) =
 | 
				
			||||||
    isTimeCommand (T_NormalWord _ [T_Literal _ "time"]) = True
 | 
					        if isCommand list cmd
 | 
				
			||||||
    isTimeCommand _ = False
 | 
					        then action
 | 
				
			||||||
 | 
					        else getParser def cmd rest
 | 
				
			||||||
 | 
					
 | 
				
			||||||
prop_readPipeline = isOk readPipeline "! cat /etc/issue | grep -i ubuntu"
 | 
					prop_readPipeline = isOk readPipeline "! cat /etc/issue | grep -i ubuntu"
 | 
				
			||||||
prop_readPipeline2 = isWarning readPipeline "!cat /etc/issue | grep -i ubuntu"
 | 
					prop_readPipeline2 = isWarning readPipeline "!cat /etc/issue | grep -i ubuntu"
 | 
				
			||||||
@@ -1782,6 +1782,22 @@ readTimeSuffix = do
 | 
				
			|||||||
        lookAhead $ char '-'
 | 
					        lookAhead $ char '-'
 | 
				
			||||||
        readCmdWord
 | 
					        readCmdWord
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- Fixme: this is a hack that doesn't handle let '++c' or let a\>b
 | 
				
			||||||
 | 
					readLetSuffix = many1 (readIoRedirect <|> try readLetExpression <|> readCmdWord)
 | 
				
			||||||
 | 
					  where
 | 
				
			||||||
 | 
					    readLetExpression = do
 | 
				
			||||||
 | 
					        startPos <- getPosition
 | 
				
			||||||
 | 
					        expression <- readStringForParser readCmdWord
 | 
				
			||||||
 | 
					        subParse startPos readArithmeticContents expression
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- Get whatever a parser would parse as a string
 | 
				
			||||||
 | 
					readStringForParser parser = do
 | 
				
			||||||
 | 
					    pos <- lookAhead (parser >> getPosition)
 | 
				
			||||||
 | 
					    s <- readUntil pos
 | 
				
			||||||
 | 
					    return s
 | 
				
			||||||
 | 
					  where
 | 
				
			||||||
 | 
					    readUntil endPos = anyChar `reluctantlyTill` (getPosition >>= guard . (== endPos))
 | 
				
			||||||
 | 
					
 | 
				
			||||||
prop_readAssignmentWord = isOk readAssignmentWord "a=42"
 | 
					prop_readAssignmentWord = isOk readAssignmentWord "a=42"
 | 
				
			||||||
prop_readAssignmentWord2 = isOk readAssignmentWord "b=(1 2 3)"
 | 
					prop_readAssignmentWord2 = isOk readAssignmentWord "b=(1 2 3)"
 | 
				
			||||||
prop_readAssignmentWord3 = isWarning readAssignmentWord "$b = 13"
 | 
					prop_readAssignmentWord3 = isWarning readAssignmentWord "$b = 13"
 | 
				
			||||||
 
 | 
				
			|||||||
		Reference in New Issue
	
	Block a user