Skip SC2214 if variable is modified in loop (fixes #2351)
This commit is contained in:
parent
3aedda766d
commit
c3aaa27540
src/ShellCheck
|
@ -1957,17 +1957,9 @@ subshellAssignmentCheck params t =
|
||||||
|
|
||||||
findSubshelled [] _ _ = return ()
|
findSubshelled [] _ _ = return ()
|
||||||
findSubshelled (Assignment x@(_, _, str, data_):rest) scopes@((reason,scope):restscope) deadVars =
|
findSubshelled (Assignment x@(_, _, str, data_):rest) scopes@((reason,scope):restscope) deadVars =
|
||||||
if isTrueAssignment data_
|
if isTrueAssignmentSource data_
|
||||||
then findSubshelled rest ((reason, x:scope):restscope) $ Map.insert str Alive deadVars
|
then findSubshelled rest ((reason, x:scope):restscope) $ Map.insert str Alive deadVars
|
||||||
else findSubshelled rest scopes deadVars
|
else findSubshelled rest scopes deadVars
|
||||||
where
|
|
||||||
isTrueAssignment c =
|
|
||||||
case c of
|
|
||||||
DataString SourceChecked -> False
|
|
||||||
DataString SourceDeclaration -> False
|
|
||||||
DataArray SourceChecked -> False
|
|
||||||
DataArray SourceDeclaration -> False
|
|
||||||
_ -> True
|
|
||||||
|
|
||||||
findSubshelled (Reference (_, readToken, str):rest) scopes deadVars = do
|
findSubshelled (Reference (_, readToken, str):rest) scopes deadVars = do
|
||||||
unless (shouldIgnore str) $ case Map.findWithDefault Alive str deadVars of
|
unless (shouldIgnore str) $ case Map.findWithDefault Alive str deadVars of
|
||||||
|
|
|
@ -1005,6 +1005,23 @@ isUnmodifiedParameterExpansion t =
|
||||||
in getBracedReference str == str
|
in getBracedReference str == str
|
||||||
_ -> False
|
_ -> False
|
||||||
|
|
||||||
|
isTrueAssignmentSource c =
|
||||||
|
case c of
|
||||||
|
DataString SourceChecked -> False
|
||||||
|
DataString SourceDeclaration -> False
|
||||||
|
DataArray SourceChecked -> False
|
||||||
|
DataArray SourceDeclaration -> False
|
||||||
|
_ -> True
|
||||||
|
|
||||||
|
modifiesVariable params token name =
|
||||||
|
or $ map check flow
|
||||||
|
where
|
||||||
|
flow = getVariableFlow params token
|
||||||
|
check t =
|
||||||
|
case t of
|
||||||
|
Assignment (_, _, n, source) -> isTrueAssignmentSource source && n == name
|
||||||
|
_ -> False
|
||||||
|
|
||||||
|
|
||||||
return []
|
return []
|
||||||
runTests = $( [| $(forAllProperties) (quickCheckWithResult (stdArgs { maxSuccess = 1 }) ) |])
|
runTests = $( [| $(forAllProperties) (quickCheckWithResult (stdArgs { maxSuccess = 1 }) ) |])
|
||||||
|
|
|
@ -961,11 +961,13 @@ prop_checkWhileGetoptsCase4 = verifyNot checkWhileGetoptsCase "while getopts 'a:
|
||||||
prop_checkWhileGetoptsCase5 = verifyNot checkWhileGetoptsCase "while getopts 'a:' x; do case $x in a) foo;; \\?) bar;; *) baz;; esac; done"
|
prop_checkWhileGetoptsCase5 = verifyNot checkWhileGetoptsCase "while getopts 'a:' x; do case $x in a) foo;; \\?) bar;; *) baz;; esac; done"
|
||||||
prop_checkWhileGetoptsCase6 = verifyNot checkWhileGetoptsCase "while getopts 'a:b' x; do case $y in a) foo;; esac; done"
|
prop_checkWhileGetoptsCase6 = verifyNot checkWhileGetoptsCase "while getopts 'a:b' x; do case $y in a) foo;; esac; done"
|
||||||
prop_checkWhileGetoptsCase7 = verifyNot checkWhileGetoptsCase "while getopts 'a:b' x; do case x$x in xa) foo;; xb) foo;; esac; done"
|
prop_checkWhileGetoptsCase7 = verifyNot checkWhileGetoptsCase "while getopts 'a:b' x; do case x$x in xa) foo;; xb) foo;; esac; done"
|
||||||
|
prop_checkWhileGetoptsCase8 = verifyNot checkWhileGetoptsCase "while getopts 'a:b' x; do x=a; case $x in a) foo;; esac; done"
|
||||||
checkWhileGetoptsCase = CommandCheck (Exactly "getopts") f
|
checkWhileGetoptsCase = CommandCheck (Exactly "getopts") f
|
||||||
where
|
where
|
||||||
f :: Token -> Analysis
|
f :: Token -> Analysis
|
||||||
f t@(T_SimpleCommand _ _ (cmd:arg1:name:_)) = do
|
f t@(T_SimpleCommand _ _ (cmd:arg1:name:_)) = do
|
||||||
path <- getPathM t
|
path <- getPathM t
|
||||||
|
params <- ask
|
||||||
sequence_ $ do
|
sequence_ $ do
|
||||||
options <- getLiteralString arg1
|
options <- getLiteralString arg1
|
||||||
getoptsVar <- getLiteralString name
|
getoptsVar <- getLiteralString name
|
||||||
|
@ -977,6 +979,9 @@ checkWhileGetoptsCase = CommandCheck (Exactly "getopts") f
|
||||||
[T_Literal _ caseVar] <- return $ getWordParts bracedWord
|
[T_Literal _ caseVar] <- return $ getWordParts bracedWord
|
||||||
guard $ caseVar == getoptsVar
|
guard $ caseVar == getoptsVar
|
||||||
|
|
||||||
|
-- Make sure the variable isn't modified
|
||||||
|
guard . not $ modifiesVariable params (T_BraceGroup (Id 0) body) getoptsVar
|
||||||
|
|
||||||
return $ check (getId arg1) (map (:[]) $ filter (/= ':') options) caseCmd
|
return $ check (getId arg1) (map (:[]) $ filter (/= ':') options) caseCmd
|
||||||
f _ = return ()
|
f _ = return ()
|
||||||
|
|
||||||
|
|
Loading…
Reference in New Issue