mirror of
https://github.com/koalaman/shellcheck
synced 2025-07-07 13:31:36 -07:00
It used to only treat all trailing variables in read as varaible declarings, but an array variable can be declared in other positions: read -a foo -r foo is a declared variable, and multiple such variables can be declared.
This commit is contained in:
parent
165e408114
commit
07f04e13ce
2 changed files with 25 additions and 4 deletions
|
@ -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
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue