Skip to content

Commit 78e55d4

Browse files
authored
Use Set.member instead of Foldable.elem (#4128)
1 parent a2a9991 commit 78e55d4

File tree

11 files changed

+15
-14
lines changed

11 files changed

+15
-14
lines changed

ghcide/session-loader/Development/IDE/Session.hs

+3-3
Original file line numberDiff line numberDiff line change
@@ -495,14 +495,14 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
495495
-- 'TargetFile Foo.hs' in the 'knownTargetsVar', thus not find 'TargetFile Foo.hs-boot'
496496
-- and also not find 'TargetModule Foo'.
497497
fs <- filterM (IO.doesFileExist . fromNormalizedFilePath) targetLocations
498-
pure $ map (\fp -> (TargetFile fp, [fp])) (nubOrd (f:fs))
498+
pure $ map (\fp -> (TargetFile fp, Set.singleton fp)) (nubOrd (f:fs))
499499
TargetModule _ -> do
500500
found <- filterM (IO.doesFileExist . fromNormalizedFilePath) targetLocations
501-
return [(targetTarget, found)]
501+
return [(targetTarget, Set.fromList found)]
502502
hasUpdate <- join $ atomically $ do
503503
known <- readTVar knownTargetsVar
504504
let known' = flip mapHashed known $ \k ->
505-
HM.unionWith (<>) k $ HM.fromList $ map (second Set.fromList) knownTargets
505+
HM.unionWith (<>) k $ HM.fromList knownTargets
506506
hasUpdate = if known /= known' then Just (unhashed known') else Nothing
507507
writeTVar knownTargetsVar known'
508508
logDirtyKeys <- recordDirtyKeys extras GetKnownTargets [emptyFilePath]

ghcide/src/Development/IDE/LSP/LanguageServer.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -155,7 +155,7 @@ setupLSP recorder getHieDbLoc userHandlers getIdeState clientMsgVar = do
155155
-- We want to avoid that the list of cancelled requests
156156
-- keeps growing if we receive cancellations for requests
157157
-- that do not exist or have already been processed.
158-
when (reqId `elem` queued) $
158+
when (reqId `Set.member` queued) $
159159
modifyTVar cancelledRequests (Set.insert reqId)
160160
let clearReqId reqId = atomically $ do
161161
modifyTVar pendingRequests (Set.delete reqId)

ghcide/src/Development/IDE/Types/Exports.hs

+2-2
Original file line numberDiff line numberDiff line change
@@ -207,7 +207,7 @@ identInfoToKeyVal identInfo =
207207

208208
buildModuleExportMap:: [(ModuleName, HashSet IdentInfo)] -> ModuleNameEnv (HashSet IdentInfo)
209209
buildModuleExportMap exportsMap = do
210-
let lst = concatMap (Set.toList. snd) exportsMap
210+
let lst = concatMap (Set.toList . snd) exportsMap
211211
let lstThree = map identInfoToKeyVal lst
212212
sortAndGroup lstThree
213213

@@ -223,4 +223,4 @@ extractModuleExports modIFace = do
223223
(modName, functionSet)
224224

225225
sortAndGroup :: [(ModuleName, IdentInfo)] -> ModuleNameEnv (HashSet IdentInfo)
226-
sortAndGroup assocs = listToUFM_C (<>) [(k, Set.fromList [v]) | (k, v) <- assocs]
226+
sortAndGroup assocs = listToUFM_C (<>) [(k, Set.singleton v) | (k, v) <- assocs]

ghcide/test/src/Development/IDE/Test.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -175,7 +175,7 @@ expectCurrentDiagnostics doc expected = do
175175

176176
checkDiagnosticsForDoc :: HasCallStack => TextDocumentIdentifier -> [(DiagnosticSeverity, Cursor, T.Text)] -> [Diagnostic] -> Session ()
177177
checkDiagnosticsForDoc TextDocumentIdentifier {_uri} expected obtained = do
178-
let expected' = Map.fromList [(nuri, map (\(ds, c, t) -> (ds, c, t, Nothing)) expected)]
178+
let expected' = Map.singleton nuri (map (\(ds, c, t) -> (ds, c, t, Nothing)) expected)
179179
nuri = toNormalizedUri _uri
180180
expectDiagnosticsWithTags' (return (_uri, obtained)) expected'
181181

plugins/hls-alternate-number-format-plugin/src/Ide/Plugin/AlternateNumberFormat.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -112,7 +112,7 @@ codeActionHandler state pId (CodeActionParams _ _ docId currRange _) = do
112112
mkWorkspaceEdit :: NormalizedFilePath -> [TextEdit] -> WorkspaceEdit
113113
mkWorkspaceEdit nfp edits = WorkspaceEdit changes Nothing Nothing
114114
where
115-
changes = Just $ Map.fromList [(filePathToUri $ fromNormalizedFilePath nfp, edits)]
115+
changes = Just $ Map.singleton (filePathToUri $ fromNormalizedFilePath nfp) edits
116116

117117
mkCodeActionTitle :: Literal -> AlternateFormat -> [GhcExtension] -> Text
118118
mkCodeActionTitle lit (alt, ext) ghcExts

plugins/hls-code-range-plugin/src/Ide/Plugin/CodeRange/ASTPreProcess.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -174,7 +174,7 @@ isIdentADef outerSpan (span, detail) =
174174
&& isDef
175175
where
176176
isDef :: Bool
177-
isDef = any isContextInfoDef . toList . identInfo $ detail
177+
isDef = any isContextInfoDef $ identInfo detail
178178

179179
-- Determines if the 'ContextInfo' represents a variable/function definition
180180
isContextInfoDef :: ContextInfo -> Bool

plugins/hls-eval-plugin/src/Ide/Plugin/Eval/CodeLens.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -228,7 +228,7 @@ runEvalCmd plId st mtoken EvalParams{..} =
228228
evalGhcEnv final_hscEnv $ do
229229
runTests evalCfg (st, fp) tests
230230

231-
let workspaceEditsMap = Map.fromList [(_uri, addFinalReturn mdlText edits)]
231+
let workspaceEditsMap = Map.singleton _uri (addFinalReturn mdlText edits)
232232
let workspaceEdits = WorkspaceEdit (Just workspaceEditsMap) Nothing Nothing
233233

234234
return workspaceEdits

plugins/hls-explicit-imports-plugin/src/Ide/Plugin/ExplicitImports.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -232,7 +232,7 @@ resolveWTextEdit ideState (RefineAll uri) = do
232232
pure $ mkWorkspaceEdit uri edits pm
233233
mkWorkspaceEdit :: Uri -> [ImportEdit] -> PositionMapping -> WorkspaceEdit
234234
mkWorkspaceEdit uri edits pm =
235-
WorkspaceEdit {_changes = Just $ Map.fromList [(uri, mapMaybe toWEdit edits)]
235+
WorkspaceEdit {_changes = Just $ Map.singleton uri (mapMaybe toWEdit edits)
236236
, _documentChanges = Nothing
237237
, _changeAnnotations = Nothing}
238238
where toWEdit ImportEdit{ieRange, ieText} =

plugins/hls-qualify-imported-names-plugin/src/Ide/Plugin/QualifyImportedNames.hs

+2-1
Original file line numberDiff line numberDiff line change
@@ -17,6 +17,7 @@ import Data.List (sortOn)
1717
import qualified Data.List as List
1818
import qualified Data.Map.Strict as Map
1919
import Data.Maybe (fromMaybe, isJust, mapMaybe)
20+
import qualified Data.Set as Set
2021
import Data.Text (Text)
2122
import qualified Data.Text as Text
2223
import Development.IDE (spanContainsRange)
@@ -164,7 +165,7 @@ refMapToUsedIdentifiers = DList.toList . Map.foldlWithKey' folder DList.empty
164165
getUsedIdentifier identifier span IdentifierDetails {..}
165166
| Just identifierSpan <- realSrcSpanToIdentifierSpan span
166167
, Right name <- identifier
167-
, Use `elem` identInfo = Just $ UsedIdentifier name identifierSpan
168+
, Use `Set.member` identInfo = Just $ UsedIdentifier name identifierSpan
168169
| otherwise = Nothing
169170

170171
updateColOffset :: Int -> Int -> Int -> Int

plugins/hls-retrie-plugin/test/Main.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -74,7 +74,7 @@ codeActionTitle _ = Nothing
7474

7575
goldenWithRetrie :: TestName -> FilePath -> (TextDocumentIdentifier -> Session ()) -> TestTree
7676
goldenWithRetrie title path act =
77-
goldenWithHaskellDoc (def { plugins = M.fromList [("retrie", def)] }) testPlugins title testDataDir path "expected" "hs" act
77+
goldenWithHaskellDoc (def { plugins = M.singleton "retrie" def }) testPlugins title testDataDir path "expected" "hs" act
7878

7979
runWithRetrie :: Session a -> IO a
8080
runWithRetrie = runSessionWithServer def testPlugins testDataDir

plugins/hls-stan-plugin/src/Ide/Plugin/Stan.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -148,7 +148,7 @@ rules recorder plId = do
148148
FiascoL es -> do
149149
logWith recorder Development.IDE.Warning (LogWarnConf es)
150150
-- If we can't read the config file, default to using all inspections:
151-
let allInspections = HM.fromList [(relativeHsFilePath, inspectionsIds)]
151+
let allInspections = HM.singleton relativeHsFilePath inspectionsIds
152152
pure (allInspections, [])
153153
ResultL _warnings stanConfig -> do
154154
-- HashMap of *relative* file paths to info about enabled checks for those file paths.

0 commit comments

Comments
 (0)