summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorVidar Holen <vidar@vidarholen.net>2018-09-15 12:33:58 -0700
committerGitHub <noreply@github.com>2018-09-15 12:33:58 -0700
commita06d7c1841737213e2e532b2cc7607c3d82eb929 (patch)
treea6bce22ef133a7cb62646b92fadd2f62abebbf6e
parent5202072a3439935fbc5a9b92fe66833633f63437 (diff)
parent07f04e13cee63425972fe70a8287c031e611cb0b (diff)
Merge pull request #1324 from ngzhian/679
Understand array variable declaration in read (fixes #679)
-rw-r--r--src/ShellCheck/Analytics.hs2
-rw-r--r--src/ShellCheck/AnalyzerLib.hs27
2 files changed, 25 insertions, 4 deletions
diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs
index 7cab7e8..394dee4 100644
--- a/src/ShellCheck/Analytics.hs
+++ b/src/ShellCheck/Analytics.hs
@@ -710,6 +710,7 @@ prop_checkArrayWithoutIndex5 = verifyTree checkArrayWithoutIndex "a[0]=foo; echo
prop_checkArrayWithoutIndex6 = verifyTree checkArrayWithoutIndex "echo $PIPESTATUS"
prop_checkArrayWithoutIndex7 = verifyTree checkArrayWithoutIndex "a=(a b); a+=c"
prop_checkArrayWithoutIndex8 = verifyTree checkArrayWithoutIndex "declare -a foo; foo=bar;"
+prop_checkArrayWithoutIndex9 = verifyTree checkArrayWithoutIndex "read -r -a arr <<< 'foo bar'; echo \"$arr\""
checkArrayWithoutIndex params _ =
doVariableFlowAnalysis readF writeF defaultMap (variableFlow params)
where
@@ -1880,6 +1881,7 @@ prop_checkUnassignedReferences32= verifyNotTree checkUnassignedReferences "if [[
prop_checkUnassignedReferences33= verifyNotTree checkUnassignedReferences "f() { local -A foo; echo \"${foo[@]}\"; }"
prop_checkUnassignedReferences34= verifyNotTree checkUnassignedReferences "declare -A foo; (( foo[bar] ))"
prop_checkUnassignedReferences35= verifyNotTree checkUnassignedReferences "echo ${arr[foo-bar]:?fail}"
+prop_checkUnassignedReferences36= verifyNotTree checkUnassignedReferences "read -a foo -r <<<\"foo bar\"; echo \"$foo\""
checkUnassignedReferences params t = warnings
where
(readMap, writeMap) = execState (mapM tally $ variableFlow params) (Map.empty, Map.empty)
diff --git a/src/ShellCheck/AnalyzerLib.hs b/src/ShellCheck/AnalyzerLib.hs
index e12588b..5820cc7 100644
--- a/src/ShellCheck/AnalyzerLib.hs
+++ b/src/ShellCheck/AnalyzerLib.hs
@@ -525,12 +525,22 @@ getReferencedVariableCommand base@(T_SimpleCommand _ _ (T_NormalWord _ (T_Litera
getReferencedVariableCommand _ = []
+-- The function returns a tuple consisting of four items describing an assignment.
+-- Given e.g. declare foo=bar
+-- (
+-- BaseCommand :: Token, -- The command/structure assigning the variable, i.e. declare foo=bar
+-- AssignmentToken :: Token, -- The specific part that assigns this variable, i.e. foo=bar
+-- VariableName :: String, -- The variable name, i.e. foo
+-- VariableValue :: DataType -- A description of the value being assigned, i.e. "Literal string with value foo"
+-- )
getModifiedVariableCommand base@(T_SimpleCommand _ _ (T_NormalWord _ (T_Literal _ x:_):rest)) =
filter (\(_,_,s,_) -> not ("-" `isPrefixOf` s)) $
case x of
"read" ->
- let params = map getLiteral rest in
- catMaybes . takeWhile isJust . reverse $ params
+ let params = map getLiteral rest
+ readArrayVars = getReadArrayVariables rest
+ in
+ catMaybes . (++ readArrayVars) . takeWhile isJust . reverse $ params
"getopts" ->
case rest of
opts:var:_ -> maybeToList $ getLiteral var
@@ -573,10 +583,14 @@ getModifiedVariableCommand base@(T_SimpleCommand _ _ (T_NormalWord _ (T_Literal
where
defaultType = if any (`elem` flags) ["a", "A"] then DataArray else DataString
- getLiteral t = do
+ getLiteralOfDataType t d = do
s <- getLiteralString t
when ("-" `isPrefixOf` s) $ fail "argument"
- return (base, t, s, DataString SourceExternal)
+ return (base, t, s, d)
+
+ getLiteral t = getLiteralOfDataType t (DataString SourceExternal)
+
+ getLiteralArray t = getLiteralOfDataType t (DataArray SourceExternal)
getModifierParamString = getModifierParam DataString
@@ -618,6 +632,11 @@ getModifiedVariableCommand base@(T_SimpleCommand _ _ (T_NormalWord _ (T_Literal
guard $ isVariableName name
return (base, lastArg, name, DataArray SourceExternal)
+ -- get all the array variables used in read, e.g. read -a arr
+ getReadArrayVariables args = do
+ map (getLiteralArray . snd)
+ (filter (\(x,_) -> getLiteralString x == Just "-a") (zip (args) (tail args)))
+
getModifiedVariableCommand _ = []
getIndexReferences s = fromMaybe [] $ do