Skip to content

Commit 98b8dc0

Browse files
committedJul 7, 2024·
Use fromList instead of reimplementing it in terms of foldl
1 parent 95c0cc2 commit 98b8dc0

File tree

2 files changed

+5
-17
lines changed

2 files changed

+5
-17
lines changed
 

‎src/ShellCheck/Analytics.hs

+4-16
Original file line numberDiff line numberDiff line change
@@ -496,10 +496,7 @@ checkWrongArithmeticAssignment params (T_SimpleCommand id [T_Assignment _ _ _ _
496496
"Use $((..)) for arithmetics, e.g. i=$((i " ++ op ++ " 2))"
497497
where
498498
regex = mkRegex "^([_a-zA-Z][_a-zA-Z0-9]*)([+*-]).+$"
499-
references = foldl (flip ($)) S.empty (map insertRef $ variableFlow params)
500-
insertRef (Assignment (_, _, name, _)) =
501-
S.insert name
502-
insertRef _ = Prelude.id
499+
references = S.fromList [name | Assignment (_, _, name, _) <- variableFlow params]
503500

504501
getNormalString (T_NormalWord _ words) = do
505502
parts <- mapM getLiterals words
@@ -2380,15 +2377,9 @@ prop_checkUnused51 = verifyTree checkUnusedAssignments "x[y[z=1]]=1; echo ${x[@]
23802377
checkUnusedAssignments params t = execWriter (mapM_ warnFor unused)
23812378
where
23822379
flow = variableFlow params
2383-
references = foldl (flip ($)) defaultMap (map insertRef flow)
2384-
insertRef (Reference (base, token, name)) =
2385-
Map.insert (stripSuffix name) ()
2386-
insertRef _ = id
2380+
references = Map.union (Map.fromList [(stripSuffix name, ()) | Reference (base, token, name) <- flow]) defaultMap
23872381

2388-
assignments = foldl (flip ($)) Map.empty (map insertAssignment flow)
2389-
insertAssignment (Assignment (_, token, name, _)) | isVariableName name =
2390-
Map.insert name token
2391-
insertAssignment _ = id
2382+
assignments = Map.fromList [(name, token) | Assignment (_, token, name, _) <- flow, isVariableName name]
23922383

23932384
unused = Map.assocs $ Map.difference assignments references
23942385

@@ -3971,10 +3962,7 @@ checkTranslatedStringVariable params (T_DollarDoubleQuoted id [T_Literal _ s])
39713962
&& S.member s assignments
39723963
= warnWithFix id 2256 "This translated string is the name of a variable. Flip leading $ and \" if this should be a quoted substitution." (fix id)
39733964
where
3974-
assignments = foldl (flip ($)) S.empty (map insertAssignment $ variableFlow params)
3975-
insertAssignment (Assignment (_, _, name, _)) | isVariableName name =
3976-
S.insert name
3977-
insertAssignment _ = Prelude.id
3965+
assignments = S.fromList [name | Assignment (_, _, name, _) <- variableFlow params, isVariableName name]
39783966
fix id = fixWith [replaceStart id params 2 "\"$"]
39793967
checkTranslatedStringVariable _ _ = return ()
39803968

‎src/ShellCheck/CFGAnalysis.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -1286,7 +1286,7 @@ dataflow ctx entry = do
12861286
else do
12871287
let (next, rest) = S.deleteFindMin ps
12881288
nexts <- process states next
1289-
writeSTRef pending $ foldl (flip S.insert) rest nexts
1289+
writeSTRef pending $ S.union (S.fromList nexts) rest
12901290
f (n-1) pending states
12911291

12921292
process states node = do

0 commit comments

Comments
 (0)