diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index 787a501..912fab5 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -1957,17 +1957,9 @@ subshellAssignmentCheck params t = findSubshelled [] _ _ = return () 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 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 unless (shouldIgnore str) $ case Map.findWithDefault Alive str deadVars of diff --git a/src/ShellCheck/AnalyzerLib.hs b/src/ShellCheck/AnalyzerLib.hs index be54fbb..e36a14f 100644 --- a/src/ShellCheck/AnalyzerLib.hs +++ b/src/ShellCheck/AnalyzerLib.hs @@ -1005,6 +1005,23 @@ isUnmodifiedParameterExpansion t = in getBracedReference str == str _ -> 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 [] runTests = $( [| $(forAllProperties) (quickCheckWithResult (stdArgs { maxSuccess = 1 }) ) |]) diff --git a/src/ShellCheck/Checks/Commands.hs b/src/ShellCheck/Checks/Commands.hs index edc41ed..e80ed3a 100644 --- a/src/ShellCheck/Checks/Commands.hs +++ b/src/ShellCheck/Checks/Commands.hs @@ -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_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_checkWhileGetoptsCase8 = verifyNot checkWhileGetoptsCase "while getopts 'a:b' x; do x=a; case $x in a) foo;; esac; done" checkWhileGetoptsCase = CommandCheck (Exactly "getopts") f where f :: Token -> Analysis f t@(T_SimpleCommand _ _ (cmd:arg1:name:_)) = do path <- getPathM t + params <- ask sequence_ $ do options <- getLiteralString arg1 getoptsVar <- getLiteralString name @@ -977,6 +979,9 @@ checkWhileGetoptsCase = CommandCheck (Exactly "getopts") f [T_Literal _ caseVar] <- return $ getWordParts bracedWord 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 f _ = return ()