Skip to content

Commit d16bf41

Browse files
committed
Better support arrays in arithmetic contexts. Fixes #1074
1 parent 8d5e3a8 commit d16bf41

File tree

5 files changed

+34
-36
lines changed

5 files changed

+34
-36
lines changed

ShellCheck/AST.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -37,8 +37,8 @@ newtype Root = Root Token
3737
data Token =
3838
TA_Binary Id String Token Token
3939
| TA_Assignment Id String Token Token
40+
| TA_Variable Id String [Token]
4041
| TA_Expansion Id [Token]
41-
| TA_Index Id Token
4242
| TA_Sequence Id [Token]
4343
| TA_Trinary Id Token Token Token
4444
| TA_Unary Id String Token
@@ -266,7 +266,7 @@ analyze f g i =
266266
c <- round t3
267267
return $ TA_Trinary id a b c
268268
delve (TA_Expansion id t) = dl t $ TA_Expansion id
269-
delve (TA_Index id t) = d1 t $ TA_Index id
269+
delve (TA_Variable id str t) = dl t $ TA_Variable id str
270270
delve (T_Annotation id anns t) = d1 t $ T_Annotation id anns
271271
delve (T_CoProc id var body) = d1 body $ T_CoProc id var
272272
delve (T_CoProcBody id t) = d1 t $ T_CoProcBody id
@@ -360,7 +360,6 @@ getId t = case t of
360360
TA_Sequence id _ -> id
361361
TA_Trinary id _ _ _ -> id
362362
TA_Expansion id _ -> id
363-
TA_Index id _ -> id
364363
T_ProcSub id _ _ -> id
365364
T_Glob id _ -> id
366365
T_ForArithmetic id _ _ _ _ -> id
@@ -374,6 +373,7 @@ getId t = case t of
374373
T_Include id _ _ -> id
375374
T_UnparsedIndex id _ _ -> id
376375
TC_Empty id _ -> id
376+
TA_Variable id _ _ -> id
377377

378378
blank :: Monad m => Token -> m ()
379379
blank = const $ return ()

ShellCheck/Analytics.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1141,12 +1141,10 @@ checkArithmeticDeref params t@(TA_Expansion _ [b@(T_DollarBraced id _)]) =
11411141
T_Arithmetic {} -> return normalWarning
11421142
T_DollarArithmetic {} -> return normalWarning
11431143
T_ForArithmetic {} -> return normalWarning
1144-
TA_Index {} -> return indexWarning
11451144
T_SimpleCommand {} -> return noWarning
11461145
_ -> Nothing
11471146

11481147
normalWarning = style id 2004 "$/${} is unnecessary on arithmetic variables."
1149-
indexWarning = style id 2149 "Remove $/${} for numeric index, or escape it for string."
11501148
noWarning = return ()
11511149
checkArithmeticDeref _ _ = return ()
11521150

@@ -1825,6 +1823,7 @@ prop_checkUnused34= verifyNotTree checkUnusedAssignments "foo=1; (( t = foo ));
18251823
prop_checkUnused35= verifyNotTree checkUnusedAssignments "a=foo; b=2; echo ${a:b}"
18261824
prop_checkUnused36= verifyNotTree checkUnusedAssignments "if [[ -v foo ]]; then true; fi"
18271825
prop_checkUnused37= verifyNotTree checkUnusedAssignments "fd=2; exec {fd}>&-"
1826+
prop_checkUnused38= verifyTree checkUnusedAssignments "(( a=42 ))"
18281827
checkUnusedAssignments params t = execWriter (mapM_ warnFor unused)
18291828
where
18301829
flow = variableFlow params
@@ -1880,6 +1879,7 @@ prop_checkUnassignedReferences30= verifyNotTree checkUnassignedReferences "if [[
18801879
prop_checkUnassignedReferences31= verifyNotTree checkUnassignedReferences "X=1; if [[ -v foo[$X+42] ]]; then echo ${foo[$X+42]}; fi"
18811880
prop_checkUnassignedReferences32= verifyNotTree checkUnassignedReferences "if [[ -v \"foo[1]\" ]]; then echo ${foo[@]}; fi"
18821881
prop_checkUnassignedReferences33= verifyNotTree checkUnassignedReferences "f() { local -A foo; echo \"${foo[@]}\"; }"
1882+
prop_checkUnassignedReferences34= verifyNotTree checkUnassignedReferences "declare -A foo; (( foo[bar] ))"
18831883
checkUnassignedReferences params t = warnings
18841884
where
18851885
(readMap, writeMap) = execState (mapM tally $ variableFlow params) (Map.empty, Map.empty)
@@ -2540,7 +2540,7 @@ checkLoopVariableReassignment params token =
25402540
T_ForArithmetic _
25412541
(TA_Sequence _
25422542
[TA_Assignment _ "="
2543-
(TA_Expansion _ [T_Literal _ var]) _])
2543+
(TA_Variable _ var _ ) _])
25442544
_ _ _ -> return var
25452545
_ -> fail "not loop"
25462546

ShellCheck/AnalyzerLib.hs

Lines changed: 7 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -444,15 +444,12 @@ getModifiedVariables t =
444444
c@T_SimpleCommand {} ->
445445
getModifiedVariableCommand c
446446

447-
TA_Unary _ "++|" var -> maybeToList $ do
448-
name <- getLiteralString var
449-
return (t, t, name, DataString $ SourceFrom [t])
450-
TA_Unary _ "|++" var -> maybeToList $ do
451-
name <- getLiteralString var
452-
return (t, t, name, DataString $ SourceFrom [t])
453-
TA_Assignment _ op lhs rhs -> maybeToList $ do
447+
TA_Unary _ "++|" v@(TA_Variable _ name _) ->
448+
[(t, v, name, DataString $ SourceFrom [v])]
449+
TA_Unary _ "|++" v@(TA_Variable _ name _) ->
450+
[(t, v, name, DataString $ SourceFrom [v])]
451+
TA_Assignment _ op (TA_Variable _ name _) rhs -> maybeToList $ do
454452
guard $ op `elem` ["=", "*=", "/=", "%=", "+=", "-=", "<<=", ">>=", "&=", "^=", "|="]
455-
name <- getLiteralString lhs
456453
return (t, t, name, DataString $ SourceFrom [rhs])
457454

458455
-- Count [[ -v foo ]] as an "assignment".
@@ -634,10 +631,10 @@ getReferencedVariables parents t =
634631
map (\x -> (l, l, x)) (
635632
getIndexReferences str
636633
++ getOffsetReferences (getBracedModifier str))
637-
TA_Expansion id _ ->
634+
TA_Variable id name _ ->
638635
if isArithmeticAssignment t
639636
then []
640-
else getIfReference t t
637+
else [(t, t, name)]
641638
T_Assignment id mode str _ word ->
642639
[(t, t, str) | mode == Append] ++ specialReferences str t word
643640

@@ -664,7 +661,6 @@ getReferencedVariables parents t =
664661
else []
665662

666663
literalizer t = case t of
667-
TA_Index {} -> return "" -- x[0] becomes a reference of x
668664
T_Glob _ s -> return s -- Also when parsed as globs
669665
_ -> Nothing
670666

ShellCheck/Checks/ShellSupport.hs

Lines changed: 3 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -191,11 +191,9 @@ checkBashisms = ForShell [Sh, Dash] $ \t -> do
191191
bashism (T_Glob id str) | "[^" `isInfixOf` str =
192192
warnMsg id "^ in place of ! in glob bracket expressions is"
193193

194-
bashism t@(TA_Expansion id _) | isBashism =
195-
warnMsg id $ fromJust str ++ " is"
196-
where
197-
str = getLiteralString t
198-
isBashism = isJust str && isBashVariable (fromJust str)
194+
bashism t@(TA_Variable id str _) | isBashVariable str =
195+
warnMsg id $ str ++ " is"
196+
199197
bashism t@(T_DollarBraced id token) = do
200198
mapM_ check expansion
201199
when (isBashVariable var) $

ShellCheck/Parser.hs

Lines changed: 18 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -697,31 +697,35 @@ readArithmeticContents =
697697
spacing1
698698
return (str, alt)
699699

700-
701700
readArrayIndex = do
702701
id <- getNextId
703702
char '['
704-
middle <- readArithmeticContents
703+
pos <- getPosition
704+
middle <- readStringForParser readArithmeticContents
705705
char ']'
706-
return $ TA_Index id middle
706+
return $ T_UnparsedIndex id pos middle
707707

708708
literal s = do
709709
id <- getNextId
710710
string s
711711
return $ T_Literal id s
712712

713-
readArithmeticLiteral =
714-
readArrayIndex <|> literal "#"
713+
readVariable = do
714+
id <- getNextId
715+
name <- readVariableName
716+
indices <- many readArrayIndex
717+
spacing
718+
return $ TA_Variable id name indices
715719

716720
readExpansion = do
717721
id <- getNextId
718722
pieces <- many1 $ choice [
719-
readArithmeticLiteral,
720723
readSingleQuoted,
721724
readDoubleQuoted,
722725
readNormalDollar,
723726
readBraced,
724727
readUnquotedBackTicked,
728+
literal "#",
725729
readNormalLiteral "+-*/=%^,]?:"
726730
]
727731
spacing
@@ -734,7 +738,7 @@ readArithmeticContents =
734738
spacing
735739
return s
736740

737-
readArithTerm = readGroup <|> readExpansion
741+
readArithTerm = readGroup <|> readVariable <|> readExpansion
738742

739743
readSequence = do
740744
spacing
@@ -2819,10 +2823,7 @@ readScriptFile = do
28192823

28202824
readUtf8Bom = called "Byte Order Mark" $ string "\xFEFF"
28212825

2822-
readScript = do
2823-
script <- readScriptFile
2824-
reparseIndices script
2825-
2826+
readScript = readScriptFile
28262827

28272828
-- Interactively run a parser in ghci:
28282829
-- debugParse readScript "echo 'hello world'"
@@ -2945,20 +2946,23 @@ reparseIndices root =
29452946
return $ T_Array id2 newWords
29462947
x -> return x
29472948
return $ T_Assignment id mode name newIndices newValue
2949+
f (TA_Variable id name indices) = do
2950+
newIndices <- mapM (fixAssignmentIndex name) indices
2951+
return $ TA_Variable id name newIndices
29482952
f t = return t
29492953

29502954
fixIndexElement name word =
29512955
case word of
29522956
T_IndexedElement id indices value -> do
29532957
new <- mapM (fixAssignmentIndex name) indices
29542958
return $ T_IndexedElement id new value
2955-
otherwise -> return word
2959+
_ -> return word
29562960

29572961
fixAssignmentIndex name word =
29582962
case word of
2959-
T_UnparsedIndex id pos src -> do
2963+
T_UnparsedIndex id pos src ->
29602964
parsed name pos src
2961-
otherwise -> return word
2965+
_ -> return word
29622966

29632967
parsed name pos src =
29642968
if isAssociative name

0 commit comments

Comments
 (0)