diff --git a/ghcide/session-loader/Development/IDE/Session.hs b/ghcide/session-loader/Development/IDE/Session.hs index d4224bd252..48af221f9b 100644 --- a/ghcide/session-loader/Development/IDE/Session.hs +++ b/ghcide/session-loader/Development/IDE/Session.hs @@ -495,14 +495,14 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do -- 'TargetFile Foo.hs' in the 'knownTargetsVar', thus not find 'TargetFile Foo.hs-boot' -- and also not find 'TargetModule Foo'. fs <- filterM (IO.doesFileExist . fromNormalizedFilePath) targetLocations - pure $ map (\fp -> (TargetFile fp, [fp])) (nubOrd (f:fs)) + pure $ map (\fp -> (TargetFile fp, Set.singleton fp)) (nubOrd (f:fs)) TargetModule _ -> do found <- filterM (IO.doesFileExist . fromNormalizedFilePath) targetLocations - return [(targetTarget, found)] + return [(targetTarget, Set.fromList found)] hasUpdate <- join $ atomically $ do known <- readTVar knownTargetsVar let known' = flip mapHashed known $ \k -> - HM.unionWith (<>) k $ HM.fromList $ map (second Set.fromList) knownTargets + HM.unionWith (<>) k $ HM.fromList knownTargets hasUpdate = if known /= known' then Just (unhashed known') else Nothing writeTVar knownTargetsVar known' logDirtyKeys <- recordDirtyKeys extras GetKnownTargets [emptyFilePath] diff --git a/ghcide/src/Development/IDE/LSP/LanguageServer.hs b/ghcide/src/Development/IDE/LSP/LanguageServer.hs index 737ee2875e..5663165f02 100644 --- a/ghcide/src/Development/IDE/LSP/LanguageServer.hs +++ b/ghcide/src/Development/IDE/LSP/LanguageServer.hs @@ -155,7 +155,7 @@ setupLSP recorder getHieDbLoc userHandlers getIdeState clientMsgVar = do -- We want to avoid that the list of cancelled requests -- keeps growing if we receive cancellations for requests -- that do not exist or have already been processed. - when (reqId `elem` queued) $ + when (reqId `Set.member` queued) $ modifyTVar cancelledRequests (Set.insert reqId) let clearReqId reqId = atomically $ do modifyTVar pendingRequests (Set.delete reqId) diff --git a/ghcide/src/Development/IDE/Types/Exports.hs b/ghcide/src/Development/IDE/Types/Exports.hs index 716611008f..3b40ce1653 100644 --- a/ghcide/src/Development/IDE/Types/Exports.hs +++ b/ghcide/src/Development/IDE/Types/Exports.hs @@ -207,7 +207,7 @@ identInfoToKeyVal identInfo = buildModuleExportMap:: [(ModuleName, HashSet IdentInfo)] -> ModuleNameEnv (HashSet IdentInfo) buildModuleExportMap exportsMap = do - let lst = concatMap (Set.toList. snd) exportsMap + let lst = concatMap (Set.toList . snd) exportsMap let lstThree = map identInfoToKeyVal lst sortAndGroup lstThree @@ -223,4 +223,4 @@ extractModuleExports modIFace = do (modName, functionSet) sortAndGroup :: [(ModuleName, IdentInfo)] -> ModuleNameEnv (HashSet IdentInfo) -sortAndGroup assocs = listToUFM_C (<>) [(k, Set.fromList [v]) | (k, v) <- assocs] +sortAndGroup assocs = listToUFM_C (<>) [(k, Set.singleton v) | (k, v) <- assocs] diff --git a/ghcide/test/src/Development/IDE/Test.hs b/ghcide/test/src/Development/IDE/Test.hs index b6bec1733b..adaa5801c0 100644 --- a/ghcide/test/src/Development/IDE/Test.hs +++ b/ghcide/test/src/Development/IDE/Test.hs @@ -175,7 +175,7 @@ expectCurrentDiagnostics doc expected = do checkDiagnosticsForDoc :: HasCallStack => TextDocumentIdentifier -> [(DiagnosticSeverity, Cursor, T.Text)] -> [Diagnostic] -> Session () checkDiagnosticsForDoc TextDocumentIdentifier {_uri} expected obtained = do - let expected' = Map.fromList [(nuri, map (\(ds, c, t) -> (ds, c, t, Nothing)) expected)] + let expected' = Map.singleton nuri (map (\(ds, c, t) -> (ds, c, t, Nothing)) expected) nuri = toNormalizedUri _uri expectDiagnosticsWithTags' (return (_uri, obtained)) expected' diff --git a/plugins/hls-alternate-number-format-plugin/src/Ide/Plugin/AlternateNumberFormat.hs b/plugins/hls-alternate-number-format-plugin/src/Ide/Plugin/AlternateNumberFormat.hs index 09591de906..3b00d79d1b 100644 --- a/plugins/hls-alternate-number-format-plugin/src/Ide/Plugin/AlternateNumberFormat.hs +++ b/plugins/hls-alternate-number-format-plugin/src/Ide/Plugin/AlternateNumberFormat.hs @@ -112,7 +112,7 @@ codeActionHandler state pId (CodeActionParams _ _ docId currRange _) = do mkWorkspaceEdit :: NormalizedFilePath -> [TextEdit] -> WorkspaceEdit mkWorkspaceEdit nfp edits = WorkspaceEdit changes Nothing Nothing where - changes = Just $ Map.fromList [(filePathToUri $ fromNormalizedFilePath nfp, edits)] + changes = Just $ Map.singleton (filePathToUri $ fromNormalizedFilePath nfp) edits mkCodeActionTitle :: Literal -> AlternateFormat -> [GhcExtension] -> Text mkCodeActionTitle lit (alt, ext) ghcExts diff --git a/plugins/hls-code-range-plugin/src/Ide/Plugin/CodeRange/ASTPreProcess.hs b/plugins/hls-code-range-plugin/src/Ide/Plugin/CodeRange/ASTPreProcess.hs index 32dc21b111..6fa799b8d5 100644 --- a/plugins/hls-code-range-plugin/src/Ide/Plugin/CodeRange/ASTPreProcess.hs +++ b/plugins/hls-code-range-plugin/src/Ide/Plugin/CodeRange/ASTPreProcess.hs @@ -174,7 +174,7 @@ isIdentADef outerSpan (span, detail) = && isDef where isDef :: Bool - isDef = any isContextInfoDef . toList . identInfo $ detail + isDef = any isContextInfoDef $ identInfo detail -- Determines if the 'ContextInfo' represents a variable/function definition isContextInfoDef :: ContextInfo -> Bool diff --git a/plugins/hls-eval-plugin/src/Ide/Plugin/Eval/CodeLens.hs b/plugins/hls-eval-plugin/src/Ide/Plugin/Eval/CodeLens.hs index 6d840968c5..ecadce4d03 100644 --- a/plugins/hls-eval-plugin/src/Ide/Plugin/Eval/CodeLens.hs +++ b/plugins/hls-eval-plugin/src/Ide/Plugin/Eval/CodeLens.hs @@ -228,7 +228,7 @@ runEvalCmd plId st mtoken EvalParams{..} = evalGhcEnv final_hscEnv $ do runTests evalCfg (st, fp) tests - let workspaceEditsMap = Map.fromList [(_uri, addFinalReturn mdlText edits)] + let workspaceEditsMap = Map.singleton _uri (addFinalReturn mdlText edits) let workspaceEdits = WorkspaceEdit (Just workspaceEditsMap) Nothing Nothing return workspaceEdits diff --git a/plugins/hls-explicit-imports-plugin/src/Ide/Plugin/ExplicitImports.hs b/plugins/hls-explicit-imports-plugin/src/Ide/Plugin/ExplicitImports.hs index 8b66538308..2c599b5b6b 100644 --- a/plugins/hls-explicit-imports-plugin/src/Ide/Plugin/ExplicitImports.hs +++ b/plugins/hls-explicit-imports-plugin/src/Ide/Plugin/ExplicitImports.hs @@ -232,7 +232,7 @@ resolveWTextEdit ideState (RefineAll uri) = do pure $ mkWorkspaceEdit uri edits pm mkWorkspaceEdit :: Uri -> [ImportEdit] -> PositionMapping -> WorkspaceEdit mkWorkspaceEdit uri edits pm = - WorkspaceEdit {_changes = Just $ Map.fromList [(uri, mapMaybe toWEdit edits)] + WorkspaceEdit {_changes = Just $ Map.singleton uri (mapMaybe toWEdit edits) , _documentChanges = Nothing , _changeAnnotations = Nothing} where toWEdit ImportEdit{ieRange, ieText} = diff --git a/plugins/hls-qualify-imported-names-plugin/src/Ide/Plugin/QualifyImportedNames.hs b/plugins/hls-qualify-imported-names-plugin/src/Ide/Plugin/QualifyImportedNames.hs index 12609b7ee7..7027feeb99 100644 --- a/plugins/hls-qualify-imported-names-plugin/src/Ide/Plugin/QualifyImportedNames.hs +++ b/plugins/hls-qualify-imported-names-plugin/src/Ide/Plugin/QualifyImportedNames.hs @@ -17,6 +17,7 @@ import Data.List (sortOn) import qualified Data.List as List import qualified Data.Map.Strict as Map import Data.Maybe (fromMaybe, isJust, mapMaybe) +import qualified Data.Set as Set import Data.Text (Text) import qualified Data.Text as Text import Development.IDE (spanContainsRange) @@ -164,7 +165,7 @@ refMapToUsedIdentifiers = DList.toList . Map.foldlWithKey' folder DList.empty getUsedIdentifier identifier span IdentifierDetails {..} | Just identifierSpan <- realSrcSpanToIdentifierSpan span , Right name <- identifier - , Use `elem` identInfo = Just $ UsedIdentifier name identifierSpan + , Use `Set.member` identInfo = Just $ UsedIdentifier name identifierSpan | otherwise = Nothing updateColOffset :: Int -> Int -> Int -> Int diff --git a/plugins/hls-retrie-plugin/test/Main.hs b/plugins/hls-retrie-plugin/test/Main.hs index 8487f92599..21fae51642 100644 --- a/plugins/hls-retrie-plugin/test/Main.hs +++ b/plugins/hls-retrie-plugin/test/Main.hs @@ -74,7 +74,7 @@ codeActionTitle _ = Nothing goldenWithRetrie :: TestName -> FilePath -> (TextDocumentIdentifier -> Session ()) -> TestTree goldenWithRetrie title path act = - goldenWithHaskellDoc (def { plugins = M.fromList [("retrie", def)] }) testPlugins title testDataDir path "expected" "hs" act + goldenWithHaskellDoc (def { plugins = M.singleton "retrie" def }) testPlugins title testDataDir path "expected" "hs" act runWithRetrie :: Session a -> IO a runWithRetrie = runSessionWithServer def testPlugins testDataDir diff --git a/plugins/hls-stan-plugin/src/Ide/Plugin/Stan.hs b/plugins/hls-stan-plugin/src/Ide/Plugin/Stan.hs index d288136fc7..757768a574 100644 --- a/plugins/hls-stan-plugin/src/Ide/Plugin/Stan.hs +++ b/plugins/hls-stan-plugin/src/Ide/Plugin/Stan.hs @@ -148,7 +148,7 @@ rules recorder plId = do FiascoL es -> do logWith recorder Development.IDE.Warning (LogWarnConf es) -- If we can't read the config file, default to using all inspections: - let allInspections = HM.fromList [(relativeHsFilePath, inspectionsIds)] + let allInspections = HM.singleton relativeHsFilePath inspectionsIds pure (allInspections, []) ResultL _warnings stanConfig -> do -- HashMap of *relative* file paths to info about enabled checks for those file paths.