From 6f16defc31207a71e0047026ea0f1d3d3ad0c705 Mon Sep 17 00:00:00 2001 From: Oliver Madine <30090176+OliverMadine@users.noreply.github.com> Date: Tue, 29 Mar 2022 03:18:33 +0100 Subject: [PATCH 01/20] refactor rename plugin - add context to error messages - remove unnecessary unwrapping of ParsedSource - use HashSet for references - consistent naming, whitespace, indentation, imports style --- ghcide/src/Development/IDE/Spans/AtPoint.hs | 8 +- .../hls-rename-plugin/hls-rename-plugin.cabal | 5 +- .../src/Ide/Plugin/Rename.hs | 205 +++++++++--------- 3 files changed, 111 insertions(+), 107 deletions(-) diff --git a/ghcide/src/Development/IDE/Spans/AtPoint.hs b/ghcide/src/Development/IDE/Spans/AtPoint.hs index 599872cebe..0bdff4aa9b 100644 --- a/ghcide/src/Development/IDE/Spans/AtPoint.hs +++ b/ghcide/src/Development/IDE/Spans/AtPoint.hs @@ -17,7 +17,7 @@ module Development.IDE.Spans.AtPoint ( , computeTypeReferences , FOIReferences(..) , defRowToSymbolInfo - , getAstNamesAtPoint + , getNamesAtPoint , toCurrentLocation , rowToLoc ) where @@ -86,7 +86,7 @@ foiReferencesAtPoint file pos (FOIReferences asts) = case HM.lookup file asts of Nothing -> ([],[],[]) Just (HAR _ hf _ _ _,mapping) -> - let names = getAstNamesAtPoint hf pos mapping + let names = getNamesAtPoint hf pos mapping adjustedLocs = HM.foldr go [] asts go (HAR _ _ rf tr _, mapping) xs = refs ++ typerefs ++ xs where @@ -96,8 +96,8 @@ foiReferencesAtPoint file pos (FOIReferences asts) = $ concat $ mapMaybe (`M.lookup` tr) names in (names, adjustedLocs,map fromNormalizedFilePath $ HM.keys asts) -getAstNamesAtPoint :: HieASTs a -> Position -> PositionMapping -> [Name] -getAstNamesAtPoint hf pos mapping = +getNamesAtPoint :: HieASTs a -> Position -> PositionMapping -> [Name] +getNamesAtPoint hf pos mapping = concat $ pointCommand hf posFile (rights . M.keys . getNodeIds) where posFile = fromMaybe pos $ fromCurrentPosition mapping pos diff --git a/plugins/hls-rename-plugin/hls-rename-plugin.cabal b/plugins/hls-rename-plugin/hls-rename-plugin.cabal index 9768c82f8a..f07acbc954 100644 --- a/plugins/hls-rename-plugin/hls-rename-plugin.cabal +++ b/plugins/hls-rename-plugin/hls-rename-plugin.cabal @@ -1,6 +1,6 @@ cabal-version: 2.4 name: hls-rename-plugin -version: 1.0.0.1 +version: 1.0.0.2 synopsis: Rename plugin for Haskell Language Server description: Please see the README on GitHub at @@ -26,13 +26,16 @@ library , ghc , ghc-exactprint , ghcide ^>=1.6 + , hashable , hiedb , hls-plugin-api ^>=1.3 , lsp , lsp-types + , mod , syb , text , transformers + , unordered-containers default-language: Haskell2010 diff --git a/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs b/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs index b9ca9798ea..d17b642ba6 100644 --- a/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs +++ b/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs @@ -8,38 +8,41 @@ module Ide.Plugin.Rename (descriptor) where -import Control.Monad -import Control.Monad.IO.Class (MonadIO (liftIO)) +#if MIN_VERSION_ghc(9,2,1) +import GHC.Parser.Annotation +#endif + +import Control.Monad.IO.Class import Control.Monad.Trans.Class import Control.Monad.Trans.Except -import Data.Containers.ListUtils import Data.Generics -import Data.List.Extra hiding (nubOrd, replace) +import Data.HashSet (HashSet) +import qualified Data.HashSet as HS +import Data.Hashable +import Data.List.Extra import qualified Data.Map as M import Data.Maybe +import Data.Mod.Word import qualified Data.Text as T import Development.IDE hiding (pluginHandlers) import Development.IDE.Core.PositionMapping import Development.IDE.Core.Shake import Development.IDE.GHC.Compat +import Development.IDE.GHC.ExactPrint import Development.IDE.Spans.AtPoint -#if MIN_VERSION_ghc(9,2,1) -import GHC.Parser.Annotation (AnnContext, AnnList, - AnnParen, AnnPragma) -#endif -#if MIN_VERSION_ghc(9,0,1) -import GHC.Types.Name -#else -import Name -#endif -import Development.IDE.GHC.ExactPrint (GetAnnotatedParsedSource (GetAnnotatedParsedSource)) import HieDb.Query import Ide.Plugin.Config import Ide.PluginUtils import Ide.Types -import Language.Haskell.GHC.ExactPrint import Language.LSP.Server import Language.LSP.Types +import Control.Monad + +instance Hashable Location +instance Hashable Range +instance Hashable Position +instance Hashable UInt +instance Hashable (Mod a) where hash n = hash (unMod n) descriptor :: PluginId -> PluginDescriptor IdeState descriptor pluginId = (defaultPluginDescriptor pluginId) { @@ -51,138 +54,136 @@ renameProvider state pluginId (RenameParams (TextDocumentIdentifier uri) pos _pr response $ do nfp <- safeUriToNfp uri oldName <- getNameAtPos state nfp pos - workspaceRefs <- refsAtName state nfp oldName - let filesRefs = groupOn locToUri workspaceRefs - getFileEdits = ap (getSrcEdits state . renameModRefs newNameText) (locToUri . head) - fileEdits <- mapM getFileEdits filesRefs + refLocs <- refsAtName state nfp oldName + let newName = mkTcOcc $ T.unpack newNameText + filesRefs = collectWith locToUri refLocs + getFileEdit = flip $ getSrcEdit state . renameRefs newName + fileEdits <- mapM (uncurry getFileEdit) filesRefs pure $ foldl' (<>) mempty fileEdits -------------------------------------------------------------------------------- +--------------------------------------------------------------------------------------------------- -- Source renaming --- | Compute a `WorkspaceEdit` by applying a given function to the `ParsedModule` for a given `Uri`. -getSrcEdits :: +-- | Apply a function to a `ParsedSource` for a given `Uri` to compute a `WorkspaceEdit`. +getSrcEdit :: (MonadLsp config m) => IdeState -> -#if MIN_VERSION_ghc(9,0,1) - (HsModule -> HsModule) -> -#else - (HsModule GhcPs -> HsModule GhcPs) -> -#endif + (ParsedSource -> ParsedSource) -> Uri -> ExceptT String m WorkspaceEdit -getSrcEdits state updateMod uri = do +getSrcEdit state updatePs uri = do ccs <- lift getClientCapabilities nfp <- safeUriToNfp uri - annotatedAst <- - handleMaybeM "Error: could not get parsed source" $ liftIO $ runAction - "Rename.GetParsedModuleWithComments" - state - (use GetAnnotatedParsedSource nfp) - let (ps, anns) = (astA annotatedAst, annsA annotatedAst) + annAst <- handleMaybeM ("No parsed source for: " ++ show nfp) $ liftIO $ runAction + "Rename.GetAnnotatedParsedSource" + state + (use GetAnnotatedParsedSource nfp) + let (ps, anns) = (astA annAst, annsA annAst) #if !MIN_VERSION_ghc(9,2,1) let src = T.pack $ exactPrint ps anns - res = T.pack $ exactPrint (updateMod <$> ps) anns + res = T.pack $ exactPrint (updatePs ps) anns #else let src = T.pack $ exactPrint ps - res = T.pack $ exactPrint (updateMod <$> ps) + res = T.pack $ exactPrint (updatePs ps) #endif - pure $ diffText ccs (uri, src) res IncludeDeletions --- | Replace a name at every given `Location` (in a given `HsModule`) with a given new name. -renameModRefs :: - T.Text -> - [Location] -> -#if MIN_VERSION_ghc(9,0,1) - HsModule - -> HsModule -#else - HsModule GhcPs - -> HsModule GhcPs -#endif +-- | Replace names at every given `Location` (in a given `ParsedSource`) with a given new name. +renameRefs :: + OccName -> + HashSet Location -> + ParsedSource -> + ParsedSource #if MIN_VERSION_ghc(9,2,1) -renameModRefs newNameText refs = everywhere $ +renameRefs newName refs = everywhere $ -- there has to be a better way... - mkT (replace @AnnListItem) `extT` - -- replace @AnnList `extT` -- not needed - -- replace @AnnParen `extT` -- not needed - -- replace @AnnPragma `extT` -- not needed - -- replace @AnnContext `extT` -- not needed - -- replace @NoEpAnns `extT` -- not needed - replace @NameAnn + mkT (replaceLoc @AnnListItem) `extT` + -- replaceLoc @AnnList `extT` -- not needed + -- replaceLoc @AnnParen `extT` -- not needed + -- replaceLoc @AnnPragma `extT` -- not needed + -- replaceLoc @AnnContext `extT` -- not needed + -- replaceLoc @NoEpAnns `extT` -- not needed + replaceLoc @NameAnn where - replace :: forall an. Typeable an => LocatedAn an RdrName -> LocatedAn an RdrName - replace (L srcSpan oldRdrName) - | isRef (locA srcSpan) = L srcSpan $ newRdrName oldRdrName - replace lOldRdrName = lOldRdrName + replaceLoc :: forall an. Typeable an => LocatedAn an RdrName -> LocatedAn an RdrName + replaceLoc (L srcSpan oldRdrName) + | isRef (locA srcSpan) = L srcSpan $ replace oldRdrName + replaceLoc lOldRdrName = lOldRdrName #else -renameModRefs newNameText refs = everywhere $ mkT replace +renameRefs newName refs = everywhere $ mkT replaceLoc where - replace :: Located RdrName -> Located RdrName - replace (L srcSpan oldRdrName) - | isRef srcSpan = L srcSpan $ newRdrName oldRdrName - replace lOldRdrName = lOldRdrName + replaceLoc :: Located RdrName -> Located RdrName + replaceLoc (L srcSpan oldRdrName) + | isRef srcSpan = L srcSpan $ replace oldRdrName + replaceLoc lOldRdrName = lOldRdrName #endif + replace :: RdrName -> RdrName + replace (Qual modName _) = Qual modName newName + replace _ = Unqual newName + isRef :: SrcSpan -> Bool isRef = (`elem` refs) . fromJust . srcSpanToLocation - newRdrName :: RdrName -> RdrName - newRdrName oldRdrName = case oldRdrName of - Qual modName _ -> Qual modName newOccName - _ -> Unqual newOccName - - newOccName = mkTcOcc $ T.unpack newNameText -------------------------------------------------------------------------------- +--------------------------------------------------------------------------------------------------- -- Reference finding -- | Note: We only find exact name occurences (i.e. type reference "depth" is 0). -refsAtName :: IdeState -> NormalizedFilePath -> Name -> ExceptT [Char] (LspT Config IO) [Location] +refsAtName :: + MonadIO m => + IdeState -> + NormalizedFilePath -> + Name -> + ExceptT String m (HashSet Location) refsAtName state nfp name = do ShakeExtras{withHieDb} <- liftIO $ runAction "Rename.HieDb" state getShakeExtras ast <- safeGetHieAst state nfp - astRefs <- handleMaybe "Error: Could not get name AST references" $ getNameAstLocations name ast dbRefs <- case nameModule_maybe name of Nothing -> pure [] - Just mod -> liftIO $ mapMaybe rowToLoc <$> - withHieDb (\hieDb -> - findReferences - hieDb - True - (nameOccName name) - (Just $ moduleName mod) - (Just $ moduleUnit mod) - [fromNormalizedFilePath nfp] - ) - pure $ nubOrd $ astRefs ++ dbRefs - -getNameAstLocations :: Name -> (HieAstResult, PositionMapping) -> Maybe [Location] -getNameAstLocations name (HAR _ _ rm _ _, mapping) = - mapMaybe (toCurrentLocation mapping . realSrcSpanToLocation . fst) <$> M.lookup (Right name) rm - -------------------------------------------------------------------------------- + Just mod -> liftIO $ mapMaybe rowToLoc <$> withHieDb (\hieDb -> + findReferences + hieDb + True + (nameOccName name) + (Just $ moduleName mod) + (Just $ moduleUnit mod) + [fromNormalizedFilePath nfp] + ) + pure $ HS.fromList $ getNameLocs name ast ++ dbRefs + +getNameLocs :: Name -> (HieAstResult, PositionMapping) -> [Location] +getNameLocs name (HAR _ _ rm _ _, pm) = + mapMaybe (toCurrentLocation pm . realSrcSpanToLocation . fst) + (concat $ M.lookup (Right name) rm) + +--------------------------------------------------------------------------------------------------- -- Util getNameAtPos :: IdeState -> NormalizedFilePath -> Position -> ExceptT String (LspT Config IO) Name getNameAtPos state nfp pos = do - (HAR{hieAst}, mapping) <- safeGetHieAst state nfp - handleMaybe "Error: could not find name at position" $ listToMaybe $ - getAstNamesAtPoint hieAst pos mapping - -nfpToUri :: NormalizedFilePath -> Uri -nfpToUri = filePathToUri . fromNormalizedFilePath - -safeUriToNfp :: (Monad m) => Uri -> ExceptT String m NormalizedFilePath -safeUriToNfp = handleMaybe "Error: Could not get uri" . fmap toNormalizedFilePath . uriToFilePath + (HAR{hieAst}, pm) <- safeGetHieAst state nfp + handleMaybe ("No name at position: " ++ show pos) $ listToMaybe $ getNamesAtPoint hieAst pos pm safeGetHieAst :: MonadIO m => IdeState -> NormalizedFilePath -> ExceptT String m (HieAstResult, PositionMapping) -safeGetHieAst state = handleMaybeM "Error: Could not get AST" . liftIO . - runAction "Rename.GetHieAst" state . useWithStale GetHieAst +safeGetHieAst state nfp = handleMaybeM + ("No AST for file: " ++ show nfp) + (liftIO $ runAction "Rename.GetHieAst" state $ useWithStale GetHieAst nfp) + +safeUriToNfp :: (Monad m) => Uri -> ExceptT String m NormalizedFilePath +safeUriToNfp uri = handleMaybe + ("No filepath for uri: " ++ show uri) + (toNormalizedFilePath <$> uriToFilePath uri) + +-- Head is safe since groups are non-empty +collectWith :: (Hashable a, Eq a, Eq b) => (a -> b) -> HashSet a -> [(b, HashSet a)] +collectWith f = map (\a -> (f $ head a, HS.fromList a)) . groupOn f . HS.toList locToUri :: Location -> Uri locToUri (Location uri _) = uri + +nfpToUri :: NormalizedFilePath -> Uri +nfpToUri = filePathToUri . fromNormalizedFilePath From 0207037aa9258d7940af259956329c2b1f26135f Mon Sep 17 00:00:00 2001 From: Oliver Madine <30090176+OliverMadine@users.noreply.github.com> Date: Tue, 29 Mar 2022 19:17:46 +0100 Subject: [PATCH 02/20] prevent renaming of built-in syntax --- plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs b/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs index d17b642ba6..8f6fdd16d1 100644 --- a/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs +++ b/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs @@ -55,6 +55,8 @@ renameProvider state pluginId (RenameParams (TextDocumentIdentifier uri) pos _pr nfp <- safeUriToNfp uri oldName <- getNameAtPos state nfp pos refLocs <- refsAtName state nfp oldName + when (isBuiltInSyntax oldName) $ + throwE ("Invalid rename of built-in syntax: \"" ++ showName oldName ++ "\"") let newName = mkTcOcc $ T.unpack newNameText filesRefs = collectWith locToUri refLocs getFileEdit = flip $ getSrcEdit state . renameRefs newName @@ -187,3 +189,6 @@ locToUri (Location uri _) = uri nfpToUri :: NormalizedFilePath -> Uri nfpToUri = filePathToUri . fromNormalizedFilePath + +showName :: Name -> String +showName = occNameString . getOccName From 801271dc75f2f62d4a34cc7f9f5a5eb8102bd517 Mon Sep 17 00:00:00 2001 From: Oliver Madine <30090176+OliverMadine@users.noreply.github.com> Date: Tue, 29 Mar 2022 19:37:38 +0100 Subject: [PATCH 03/20] limit rename scope to current module --- .../src/Ide/Plugin/Rename.hs | 39 +++++++++++++++++-- 1 file changed, 36 insertions(+), 3 deletions(-) diff --git a/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs b/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs index 8f6fdd16d1..b5b960267e 100644 --- a/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs +++ b/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs @@ -12,6 +12,7 @@ module Ide.Plugin.Rename (descriptor) where import GHC.Parser.Annotation #endif +import Control.Monad import Control.Monad.IO.Class import Control.Monad.Trans.Class import Control.Monad.Trans.Except @@ -36,7 +37,6 @@ import Ide.PluginUtils import Ide.Types import Language.LSP.Server import Language.LSP.Types -import Control.Monad instance Hashable Location instance Hashable Range @@ -57,12 +57,36 @@ renameProvider state pluginId (RenameParams (TextDocumentIdentifier uri) pos _pr refLocs <- refsAtName state nfp oldName when (isBuiltInSyntax oldName) $ throwE ("Invalid rename of built-in syntax: \"" ++ showName oldName ++ "\"") + failWhenImportOrExport state nfp refLocs oldName let newName = mkTcOcc $ T.unpack newNameText filesRefs = collectWith locToUri refLocs getFileEdit = flip $ getSrcEdit state . renameRefs newName fileEdits <- mapM (uncurry getFileEdit) filesRefs pure $ foldl' (<>) mempty fileEdits +-- | Limitation: Renaming across modules is unsupported due limited of multi-component support. +failWhenImportOrExport :: + (MonadLsp config m) => + IdeState -> + NormalizedFilePath -> + HashSet Location -> + Name -> + ExceptT String m () +failWhenImportOrExport state nfp refLocs name = do + pm <- handleMaybeM ("No parsed module for: " ++ show nfp) $ liftIO $ runAction + "Rename.GetParsedModule" + state + (use GetParsedModule nfp) + let hsMod = unLoc $ pm_parsed_source pm + L _ modName <- handleMaybe ("No module name for: " ++ show nfp) $ hsmodName hsMod + unless (nameIsLocalOrFrom (replaceModName name modName) name) $ + throwE "Renaming of an imported name is unsupported" + case hsmodExports hsMod of + Nothing -> throwE "Explicit export list required for renaming" + Just (L _ exports) | any ((`HS.member` refLocs) . unsafeSrcSpanToLoc . getLoc) exports + -> throwE "Renaming of an exported name is unsupported" + _ -> pure () + --------------------------------------------------------------------------------------------------- -- Source renaming @@ -125,7 +149,7 @@ renameRefs newName refs = everywhere $ mkT replaceLoc replace _ = Unqual newName isRef :: SrcSpan -> Bool - isRef = (`elem` refs) . fromJust . srcSpanToLocation + isRef = (`elem` refs) . unsafeSrcSpanToLoc --------------------------------------------------------------------------------------------------- -- Reference finding @@ -180,7 +204,7 @@ safeUriToNfp uri = handleMaybe ("No filepath for uri: " ++ show uri) (toNormalizedFilePath <$> uriToFilePath uri) --- Head is safe since groups are non-empty +-- head is safe since groups are non-empty collectWith :: (Hashable a, Eq a, Eq b) => (a -> b) -> HashSet a -> [(b, HashSet a)] collectWith f = map (\a -> (f $ head a, HS.fromList a)) . groupOn f . HS.toList @@ -192,3 +216,12 @@ nfpToUri = filePathToUri . fromNormalizedFilePath showName :: Name -> String showName = occNameString . getOccName + +unsafeSrcSpanToLoc :: SrcSpan -> Location +unsafeSrcSpanToLoc srcSpan = + case srcSpanToLocation srcSpan of + Nothing -> error "Invalid conversion from UnhelpfulSpan to Location" + Just location -> location + +replaceModName :: Name -> ModuleName -> Module +replaceModName name = mkModule (moduleUnitId $ nameModule name) From 03c31abfacfbfc948a09a91e62afe04aae3944bc Mon Sep 17 00:00:00 2001 From: Oliver Madine <30090176+OliverMadine@users.noreply.github.com> Date: Tue, 29 Mar 2022 19:49:11 +0100 Subject: [PATCH 04/20] refine imports in rename plugin --- .../src/Ide/Plugin/Rename.hs | 20 ++++++++++++------- 1 file changed, 13 insertions(+), 7 deletions(-) diff --git a/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs b/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs index b5b960267e..0432de1639 100644 --- a/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs +++ b/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs @@ -17,20 +17,26 @@ import Control.Monad.IO.Class import Control.Monad.Trans.Class import Control.Monad.Trans.Except import Data.Generics -import Data.HashSet (HashSet) -import qualified Data.HashSet as HS +import Data.HashSet (HashSet) +import qualified Data.HashSet as HS import Data.Hashable -import Data.List.Extra -import qualified Data.Map as M +import Data.List.Extra (foldl', groupOn) +import qualified Data.Map as M import Data.Maybe import Data.Mod.Word -import qualified Data.Text as T -import Development.IDE hiding (pluginHandlers) +import qualified Data.Text as T import Development.IDE.Core.PositionMapping +import Development.IDE.Core.RuleTypes +import Development.IDE.Core.Service import Development.IDE.Core.Shake -import Development.IDE.GHC.Compat +import Development.IDE.GHC.Compat.Core +import Development.IDE.GHC.Compat.ExactPrint +import Development.IDE.GHC.Compat.Parser +import Development.IDE.GHC.Compat.Units +import Development.IDE.GHC.Error import Development.IDE.GHC.ExactPrint import Development.IDE.Spans.AtPoint +import Development.IDE.Types.Location import HieDb.Query import Ide.Plugin.Config import Ide.PluginUtils From 8dafdd70a849ed819728151dd077ee59e133a294 Mon Sep 17 00:00:00 2001 From: Oliver Madine <30090176+OliverMadine@users.noreply.github.com> Date: Tue, 29 Mar 2022 21:02:34 +0100 Subject: [PATCH 05/20] allow renaming with implicit module names --- .../hls-rename-plugin/src/Ide/Plugin/Rename.hs | 16 ++++++++-------- 1 file changed, 8 insertions(+), 8 deletions(-) diff --git a/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs b/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs index 0432de1639..b93d408b1e 100644 --- a/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs +++ b/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs @@ -84,13 +84,12 @@ failWhenImportOrExport state nfp refLocs name = do state (use GetParsedModule nfp) let hsMod = unLoc $ pm_parsed_source pm - L _ modName <- handleMaybe ("No module name for: " ++ show nfp) $ hsmodName hsMod - unless (nameIsLocalOrFrom (replaceModName name modName) name) $ - throwE "Renaming of an imported name is unsupported" - case hsmodExports hsMod of - Nothing -> throwE "Explicit export list required for renaming" - Just (L _ exports) | any ((`HS.member` refLocs) . unsafeSrcSpanToLoc . getLoc) exports + case (unLoc <$> hsmodName hsMod, hsmodExports hsMod) of + (mbModName, _) | not $ nameIsLocalOrFrom (replaceModName name mbModName) name + -> throwE "Renaming of an imported name is unsupported" + (_, Just (L _ exports)) | any ((`HS.member` refLocs) . unsafeSrcSpanToLoc . getLoc) exports -> throwE "Renaming of an exported name is unsupported" + (Just _, Nothing) -> throwE "Explicit export list required for renaming" _ -> pure () --------------------------------------------------------------------------------------------------- @@ -229,5 +228,6 @@ unsafeSrcSpanToLoc srcSpan = Nothing -> error "Invalid conversion from UnhelpfulSpan to Location" Just location -> location -replaceModName :: Name -> ModuleName -> Module -replaceModName name = mkModule (moduleUnitId $ nameModule name) +replaceModName :: Name -> Maybe ModuleName -> Module +replaceModName name mbModName = + mkModule (moduleUnitId $ nameModule name) (fromMaybe (mkModuleName "Main") mbModName) From b7cda24452c489c666ac4acecc7140dac64a4326 Mon Sep 17 00:00:00 2001 From: Oliver Madine <30090176+OliverMadine@users.noreply.github.com> Date: Tue, 29 Mar 2022 21:04:05 +0100 Subject: [PATCH 06/20] update tests with cross-module renaming limitation --- plugins/hls-rename-plugin/test/Main.hs | 21 ++++++++++++------- .../testdata/FunctionArgument.expected.hs | 2 +- .../test/testdata/FunctionArgument.hs | 2 +- .../test/testdata/LetExpression.expected.hs | 2 +- .../test/testdata/LetExpression.hs | 2 +- .../test/testdata/Typeclass.expected.hs | 2 +- .../test/testdata/Typeclass.hs | 2 +- 7 files changed, 20 insertions(+), 13 deletions(-) diff --git a/plugins/hls-rename-plugin/test/Main.hs b/plugins/hls-rename-plugin/test/Main.hs index 31baec621c..e0835935e6 100644 --- a/plugins/hls-rename-plugin/test/Main.hs +++ b/plugins/hls-rename-plugin/test/Main.hs @@ -16,7 +16,8 @@ tests :: TestTree tests = testGroup "Rename" [ goldenWithRename "Data constructor" "DataConstructor" $ \doc -> do rename doc (Position 0 15) "Op" - , goldenWithRename "Exported function" "ExportedFunction" $ \doc -> do + , ignoreTestBecause "Renaming across modules unsupported" $ + goldenWithRename "Exported function" "ExportedFunction" $ \doc -> do rename doc (Position 2 1) "quux" , goldenWithRename "Function argument" "FunctionArgument" $ \doc -> do rename doc (Position 3 4) "y" @@ -24,19 +25,25 @@ tests = testGroup "Rename" rename doc (Position 3 1) "baz" , goldenWithRename "GADT" "Gadt" $ \doc -> do rename doc (Position 6 37) "Expr" - , goldenWithRename "Hidden function" "HiddenFunction" $ \doc -> do + , ignoreTestBecause "Renaming across modules unsupported" $ + goldenWithRename "Hidden function" "HiddenFunction" $ \doc -> do rename doc (Position 0 32) "quux" - , goldenWithRename "Imported function" "ImportedFunction" $ \doc -> do + , ignoreTestBecause "Renaming across modules unsupported" $ + goldenWithRename "Imported function" "ImportedFunction" $ \doc -> do rename doc (Position 3 8) "baz" - , goldenWithRename "Import hiding" "ImportHiding" $ \doc -> do + , ignoreTestBecause "Renaming across modules unsupported" $ + goldenWithRename "Import hiding" "ImportHiding" $ \doc -> do rename doc (Position 0 22) "hiddenFoo" , goldenWithRename "Let expression" "LetExpression" $ \doc -> do rename doc (Position 5 11) "foobar" - , goldenWithRename "Qualified as" "QualifiedAs" $ \doc -> do + , ignoreTestBecause "Renaming across modules unsupported" $ + goldenWithRename "Qualified as" "QualifiedAs" $ \doc -> do rename doc (Position 3 10) "baz" - , goldenWithRename "Qualified shadowing" "QualifiedShadowing" $ \doc -> do + , ignoreTestBecause "Renaming across modules unsupported" $ + goldenWithRename "Qualified shadowing" "QualifiedShadowing" $ \doc -> do rename doc (Position 3 12) "foobar" - , goldenWithRename "Qualified function" "QualifiedFunction" $ \doc -> do + , ignoreTestBecause "Renaming across modules unsupported" $ + goldenWithRename "Qualified function" "QualifiedFunction" $ \doc -> do rename doc (Position 3 12) "baz" , goldenWithRename "Realigns do block indentation" "RealignDo" $ \doc -> do rename doc (Position 0 2) "fooBarQuux" diff --git a/plugins/hls-rename-plugin/test/testdata/FunctionArgument.expected.hs b/plugins/hls-rename-plugin/test/testdata/FunctionArgument.expected.hs index bd8d83b334..bc10997ece 100644 --- a/plugins/hls-rename-plugin/test/testdata/FunctionArgument.expected.hs +++ b/plugins/hls-rename-plugin/test/testdata/FunctionArgument.expected.hs @@ -1,4 +1,4 @@ -module FunctionArgument where +module FunctionArgument () where foo :: Int -> Int foo y = y + 1 diff --git a/plugins/hls-rename-plugin/test/testdata/FunctionArgument.hs b/plugins/hls-rename-plugin/test/testdata/FunctionArgument.hs index a6006e6fac..d318cd80c4 100644 --- a/plugins/hls-rename-plugin/test/testdata/FunctionArgument.hs +++ b/plugins/hls-rename-plugin/test/testdata/FunctionArgument.hs @@ -1,4 +1,4 @@ -module FunctionArgument where +module FunctionArgument () where foo :: Int -> Int foo x = x + 1 diff --git a/plugins/hls-rename-plugin/test/testdata/LetExpression.expected.hs b/plugins/hls-rename-plugin/test/testdata/LetExpression.expected.hs index 437fac2c96..213b49c20f 100644 --- a/plugins/hls-rename-plugin/test/testdata/LetExpression.expected.hs +++ b/plugins/hls-rename-plugin/test/testdata/LetExpression.expected.hs @@ -1,4 +1,4 @@ -module Let where +module Let () where import Foo diff --git a/plugins/hls-rename-plugin/test/testdata/LetExpression.hs b/plugins/hls-rename-plugin/test/testdata/LetExpression.hs index cbd5868de6..ec9f58bcea 100644 --- a/plugins/hls-rename-plugin/test/testdata/LetExpression.hs +++ b/plugins/hls-rename-plugin/test/testdata/LetExpression.hs @@ -1,4 +1,4 @@ -module Let where +module Let () where import Foo diff --git a/plugins/hls-rename-plugin/test/testdata/Typeclass.expected.hs b/plugins/hls-rename-plugin/test/testdata/Typeclass.expected.hs index 73199ec83e..6a021a3a52 100644 --- a/plugins/hls-rename-plugin/test/testdata/Typeclass.expected.hs +++ b/plugins/hls-rename-plugin/test/testdata/Typeclass.expected.hs @@ -1,4 +1,4 @@ -module Typeclass where +module Typeclass () where class Equal a where equals :: a -> a -> Bool diff --git a/plugins/hls-rename-plugin/test/testdata/Typeclass.hs b/plugins/hls-rename-plugin/test/testdata/Typeclass.hs index 57667128dd..b92a591321 100644 --- a/plugins/hls-rename-plugin/test/testdata/Typeclass.hs +++ b/plugins/hls-rename-plugin/test/testdata/Typeclass.hs @@ -1,4 +1,4 @@ -module Typeclass where +module Typeclass () where class Equality a where equals :: a -> a -> Bool From ca5f91a334f960230da9e190efb15f0c15ee8b30 Mon Sep 17 00:00:00 2001 From: Oliver Madine <30090176+OliverMadine@users.noreply.github.com> Date: Tue, 29 Mar 2022 21:29:55 +0100 Subject: [PATCH 07/20] enable rename plugin - add rename package to hackage CI - set default build flag to True --- .github/workflows/hackage.yml | 2 +- haskell-language-server.cabal | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/.github/workflows/hackage.yml b/.github/workflows/hackage.yml index 8aea5f8de4..69815a319e 100644 --- a/.github/workflows/hackage.yml +++ b/.github/workflows/hackage.yml @@ -33,7 +33,7 @@ jobs: "hls-class-plugin", "hls-eval-plugin", "hls-explicit-imports-plugin", "hls-haddock-comments-plugin", "hls-hlint-plugin", "hls-module-name-plugin", "hls-pragmas-plugin", - "hls-refine-imports-plugin", "hls-retrie-plugin", + "hls-refine-imports-plugin", "hls-rename-plugin", "hls-retrie-plugin", "hls-splice-plugin", "hls-tactics-plugin", "hls-call-hierarchy-plugin", "hls-alternate-number-format-plugin", "hls-qualify-imported-names-plugin", "hls-selection-range-plugin", diff --git a/haskell-language-server.cabal b/haskell-language-server.cabal index 13bc2de7a0..e1fe142e93 100644 --- a/haskell-language-server.cabal +++ b/haskell-language-server.cabal @@ -133,7 +133,7 @@ flag refineImports flag rename description: Enable rename plugin - default: False + default: True manual: True flag retrie From 6731ef0bbf3aaa0ad911f4b827ffbe87c27ad7c0 Mon Sep 17 00:00:00 2001 From: Oliver Madine <30090176+OliverMadine@users.noreply.github.com> Date: Tue, 29 Mar 2022 21:53:42 +0100 Subject: [PATCH 08/20] add rename plugin to features docs --- docs/features.md | 14 +++++++++++++- 1 file changed, 13 insertions(+), 1 deletion(-) diff --git a/docs/features.md b/docs/features.md index dfb0b6b516..77522fb322 100644 --- a/docs/features.md +++ b/docs/features.md @@ -19,6 +19,7 @@ Many of these are standard LSP features, but a lot of special features are provi | [Code actions](#code-actions) | `textDocument/codeAction` | | [Code lenses](#code-lenses) | `textDocument/codeLens` | | [Selection range](#selection-range) | `textDocument/selectionRange` | +| [Rename](#rename) | `textDocument/rename` | The individual sections below also identify which [HLS plugin](./what-is-hls.md#hls-plugins) is responsible for providing the given functionality, which is useful if you want to raise an issue report or contribute! Additionally, not all plugins are supported on all versions of GHC, see the [GHC version support page](supported-versions.md) for details. @@ -305,6 +306,18 @@ support. ![Selection range demo](https://user-images.githubusercontent.com/16440269/150301502-4c002605-9f8d-43f5-86d3-28846942c4ff.mov) +## Rename + +Provided by: `hls-rename-plugin` + +Provides renaming of symbols within a module. + +![Rename Demo](https://user-images.githubusercontent.com/30090176/133072143-d7d03ec7-3db1-474e-ad5e-6f40d75ff7ab.gif) + +Known limitations: + +- Only works within a module due to limited [multi-component support](https://github.com/haskell/haskell-language-server/issues/2193). + ## Missing features The following features are supported by the LSP specification but not implemented in HLS. @@ -315,7 +328,6 @@ Contributions welcome! | Signature help | Unimplemented | `textDocument/signatureHelp` | | Jump to declaration | Unclear if useful | `textDocument/declaration` | | Jump to implementation | Unclear if useful | `textDocument/implementation` | -| Renaming | [Parital implementation](https://github.com/haskell/haskell-language-server/issues/2193) | `textDocument/rename`, `textDocument/prepareRename` | | Folding | Unimplemented | `textDocument/foldingRange` | | Semantic tokens | Unimplemented | `textDocument/semanticTokens` | | Linked editing | Unimplemented | `textDocument/linkedEditingRange` | From c9ae8478e003eded638f1c101e82a9a4bff04a42 Mon Sep 17 00:00:00 2001 From: Oliver Madine <30090176+OliverMadine@users.noreply.github.com> Date: Tue, 29 Mar 2022 22:44:44 +0100 Subject: [PATCH 09/20] add rename plugin to ghc-8.10.X stack yaml files --- stack-8.10.6.yaml | 1 + stack-8.10.7.yaml | 1 + stack.yaml | 1 + 3 files changed, 3 insertions(+) diff --git a/stack-8.10.6.yaml b/stack-8.10.6.yaml index c7b8c521d3..f3641d1044 100644 --- a/stack-8.10.6.yaml +++ b/stack-8.10.6.yaml @@ -18,6 +18,7 @@ packages: - ./plugins/hls-explicit-imports-plugin - ./plugins/hls-refine-imports-plugin - ./plugins/hls-hlint-plugin + - ./plugins/hls-rename-plugin - ./plugins/hls-retrie-plugin - ./plugins/hls-splice-plugin - ./plugins/hls-tactics-plugin diff --git a/stack-8.10.7.yaml b/stack-8.10.7.yaml index d38a3e874c..ced3a1a646 100644 --- a/stack-8.10.7.yaml +++ b/stack-8.10.7.yaml @@ -19,6 +19,7 @@ packages: - ./plugins/hls-explicit-imports-plugin - ./plugins/hls-refine-imports-plugin - ./plugins/hls-hlint-plugin + - ./plugins/hls-rename-plugin - ./plugins/hls-retrie-plugin - ./plugins/hls-splice-plugin - ./plugins/hls-tactics-plugin diff --git a/stack.yaml b/stack.yaml index 5f4d0a972e..f4551e9ac4 100644 --- a/stack.yaml +++ b/stack.yaml @@ -19,6 +19,7 @@ packages: - ./plugins/hls-explicit-imports-plugin - ./plugins/hls-refine-imports-plugin - ./plugins/hls-hlint-plugin + - ./plugins/hls-rename-plugin - ./plugins/hls-retrie-plugin - ./plugins/hls-splice-plugin - ./plugins/hls-tactics-plugin From 062fe8cf022ef32b3197e83ef9a251cb31d41309 Mon Sep 17 00:00:00 2001 From: Oliver Madine <30090176+OliverMadine@users.noreply.github.com> Date: Tue, 29 Mar 2022 23:09:43 +0100 Subject: [PATCH 10/20] improve position printing in rename error --- plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs b/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs index b93d408b1e..946c5caabd 100644 --- a/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs +++ b/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs @@ -193,7 +193,7 @@ getNameLocs name (HAR _ _ rm _ _, pm) = getNameAtPos :: IdeState -> NormalizedFilePath -> Position -> ExceptT String (LspT Config IO) Name getNameAtPos state nfp pos = do (HAR{hieAst}, pm) <- safeGetHieAst state nfp - handleMaybe ("No name at position: " ++ show pos) $ listToMaybe $ getNamesAtPoint hieAst pos pm + handleMaybe ("No name at " ++ showPos pos) $ listToMaybe $ getNamesAtPoint hieAst pos pm safeGetHieAst :: MonadIO m => @@ -222,6 +222,9 @@ nfpToUri = filePathToUri . fromNormalizedFilePath showName :: Name -> String showName = occNameString . getOccName +showPos :: Position -> String +showPos Position{_line, _character} = "line: " ++ show _line ++ " - character: " ++ show _character + unsafeSrcSpanToLoc :: SrcSpan -> Location unsafeSrcSpanToLoc srcSpan = case srcSpanToLocation srcSpan of From 866d6f5b973d3817330abb3b68d3ff051f999c20 Mon Sep 17 00:00:00 2001 From: Oliver Madine <30090176+OliverMadine@users.noreply.github.com> Date: Sat, 2 Apr 2022 19:58:22 +0100 Subject: [PATCH 11/20] implement cross-module rename config option --- .../src/Ide/Plugin/Rename.hs | 26 ++++++++++++++----- 1 file changed, 20 insertions(+), 6 deletions(-) diff --git a/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs b/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs index 946c5caabd..4404f94c23 100644 --- a/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs +++ b/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs @@ -1,10 +1,12 @@ {-# LANGUAGE CPP #-} {-# LANGUAGE DataKinds #-} +{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE OverloadedLabels #-} +{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} -{-# LANGUAGE TypeApplications #-} module Ide.Plugin.Rename (descriptor) where @@ -39,6 +41,7 @@ import Development.IDE.Spans.AtPoint import Development.IDE.Types.Location import HieDb.Query import Ide.Plugin.Config +import Ide.Plugin.Properties import Ide.PluginUtils import Ide.Types import Language.LSP.Server @@ -51,9 +54,11 @@ instance Hashable UInt instance Hashable (Mod a) where hash n = hash (unMod n) descriptor :: PluginId -> PluginDescriptor IdeState -descriptor pluginId = (defaultPluginDescriptor pluginId) { - pluginHandlers = mkPluginHandler STextDocumentRename renameProvider -} +descriptor pluginId = (defaultPluginDescriptor pluginId) + { pluginHandlers = mkPluginHandler STextDocumentRename renameProvider + , pluginConfigDescriptor = defaultConfigDescriptor + { configCustomConfig = mkCustomConfig properties } + } renameProvider :: PluginMethodHandler IdeState TextDocumentRename renameProvider state pluginId (RenameParams (TextDocumentIdentifier uri) pos _prog newNameText) = @@ -61,16 +66,17 @@ renameProvider state pluginId (RenameParams (TextDocumentIdentifier uri) pos _pr nfp <- safeUriToNfp uri oldName <- getNameAtPos state nfp pos refLocs <- refsAtName state nfp oldName + crossModuleEnabled <- lift $ usePropertyLsp #crossModule pluginId properties + unless crossModuleEnabled $ failWhenImportOrExport state nfp refLocs oldName when (isBuiltInSyntax oldName) $ throwE ("Invalid rename of built-in syntax: \"" ++ showName oldName ++ "\"") - failWhenImportOrExport state nfp refLocs oldName let newName = mkTcOcc $ T.unpack newNameText filesRefs = collectWith locToUri refLocs getFileEdit = flip $ getSrcEdit state . renameRefs newName fileEdits <- mapM (uncurry getFileEdit) filesRefs pure $ foldl' (<>) mempty fileEdits --- | Limitation: Renaming across modules is unsupported due limited of multi-component support. +-- | Limit renaming across modules. failWhenImportOrExport :: (MonadLsp config m) => IdeState -> @@ -234,3 +240,11 @@ unsafeSrcSpanToLoc srcSpan = replaceModName :: Name -> Maybe ModuleName -> Module replaceModName name mbModName = mkModule (moduleUnitId $ nameModule name) (fromMaybe (mkModuleName "Main") mbModName) + +--------------------------------------------------------------------------------------------------- +-- Config + +properties :: Properties '[ 'PropertyKey "crossModule" 'TBoolean] +properties = emptyProperties + & defineBooleanProperty #crossModule + "Enable experimental cross-module renaming" False From bace426f21d5cbd376190825ae86189ff5bb4e5c Mon Sep 17 00:00:00 2001 From: Oliver Madine <30090176+OliverMadine@users.noreply.github.com> Date: Sat, 2 Apr 2022 19:58:42 +0100 Subject: [PATCH 12/20] unignore tests for cross-module renames --- .../hls-rename-plugin/hls-rename-plugin.cabal | 3 + plugins/hls-rename-plugin/test/Main.hs | 56 +++++++++---------- 2 files changed, 31 insertions(+), 28 deletions(-) diff --git a/plugins/hls-rename-plugin/hls-rename-plugin.cabal b/plugins/hls-rename-plugin/hls-rename-plugin.cabal index f07acbc954..9b6b7576e9 100644 --- a/plugins/hls-rename-plugin/hls-rename-plugin.cabal +++ b/plugins/hls-rename-plugin/hls-rename-plugin.cabal @@ -46,7 +46,10 @@ test-suite tests main-is: Main.hs ghc-options: -threaded -rtsopts -with-rtsopts=-N build-depends: + , aeson , base + , containers , filepath + , hls-plugin-api , hls-rename-plugin , hls-test-utils ^>=1.2 diff --git a/plugins/hls-rename-plugin/test/Main.hs b/plugins/hls-rename-plugin/test/Main.hs index e0835935e6..66bcea6222 100644 --- a/plugins/hls-rename-plugin/test/Main.hs +++ b/plugins/hls-rename-plugin/test/Main.hs @@ -2,6 +2,9 @@ module Main (main) where +import Data.Aeson +import qualified Data.Map as M +import Ide.Plugin.Config import qualified Ide.Plugin.Rename as Rename import System.FilePath import Test.Hls @@ -14,54 +17,51 @@ renamePlugin = Rename.descriptor "rename" tests :: TestTree tests = testGroup "Rename" - [ goldenWithRename "Data constructor" "DataConstructor" $ \doc -> do + [ goldenWithRename "Data constructor" "DataConstructor" $ \doc -> rename doc (Position 0 15) "Op" - , ignoreTestBecause "Renaming across modules unsupported" $ - goldenWithRename "Exported function" "ExportedFunction" $ \doc -> do + , goldenWithRename "Exported function" "ExportedFunction" $ \doc -> rename doc (Position 2 1) "quux" - , goldenWithRename "Function argument" "FunctionArgument" $ \doc -> do + , goldenWithRename "Function argument" "FunctionArgument" $ \doc -> rename doc (Position 3 4) "y" - , goldenWithRename "Function name" "FunctionName" $ \doc -> do + , goldenWithRename "Function name" "FunctionName" $ \doc -> rename doc (Position 3 1) "baz" - , goldenWithRename "GADT" "Gadt" $ \doc -> do + , goldenWithRename "GADT" "Gadt" $ \doc -> rename doc (Position 6 37) "Expr" - , ignoreTestBecause "Renaming across modules unsupported" $ - goldenWithRename "Hidden function" "HiddenFunction" $ \doc -> do + , goldenWithRename "Hidden function" "HiddenFunction" $ \doc -> rename doc (Position 0 32) "quux" - , ignoreTestBecause "Renaming across modules unsupported" $ - goldenWithRename "Imported function" "ImportedFunction" $ \doc -> do + , goldenWithRename "Imported function" "ImportedFunction" $ \doc -> rename doc (Position 3 8) "baz" - , ignoreTestBecause "Renaming across modules unsupported" $ - goldenWithRename "Import hiding" "ImportHiding" $ \doc -> do + , goldenWithRename "Import hiding" "ImportHiding" $ \doc -> rename doc (Position 0 22) "hiddenFoo" - , goldenWithRename "Let expression" "LetExpression" $ \doc -> do + , goldenWithRename "Let expression" "LetExpression" $ \doc -> rename doc (Position 5 11) "foobar" - , ignoreTestBecause "Renaming across modules unsupported" $ - goldenWithRename "Qualified as" "QualifiedAs" $ \doc -> do + , goldenWithRename "Qualified as" "QualifiedAs" $ \doc -> rename doc (Position 3 10) "baz" - , ignoreTestBecause "Renaming across modules unsupported" $ - goldenWithRename "Qualified shadowing" "QualifiedShadowing" $ \doc -> do + , goldenWithRename "Qualified shadowing" "QualifiedShadowing" $ \doc -> rename doc (Position 3 12) "foobar" - , ignoreTestBecause "Renaming across modules unsupported" $ - goldenWithRename "Qualified function" "QualifiedFunction" $ \doc -> do + , goldenWithRename "Qualified function" "QualifiedFunction" $ \doc -> rename doc (Position 3 12) "baz" - , goldenWithRename "Realigns do block indentation" "RealignDo" $ \doc -> do + , goldenWithRename "Realigns do block indentation" "RealignDo" $ \doc -> rename doc (Position 0 2) "fooBarQuux" - , goldenWithRename "Record field" "RecordField" $ \doc -> do + , goldenWithRename "Record field" "RecordField" $ \doc -> rename doc (Position 6 9) "number" - , goldenWithRename "Shadowed name" "ShadowedName" $ \doc -> do + , goldenWithRename "Shadowed name" "ShadowedName" $ \doc -> rename doc (Position 1 1) "baz" - , goldenWithRename "Typeclass" "Typeclass" $ \doc -> do + , goldenWithRename "Typeclass" "Typeclass" $ \doc -> rename doc (Position 8 15) "Equal" - , goldenWithRename "Type constructor" "TypeConstructor" $ \doc -> do + , goldenWithRename "Type constructor" "TypeConstructor" $ \doc -> rename doc (Position 2 17) "BinaryTree" - , goldenWithRename "Type variable" "TypeVariable" $ \doc -> do + , goldenWithRename "Type variable" "TypeVariable" $ \doc -> rename doc (Position 0 13) "b" ] -goldenWithRename :: TestName -> FilePath -> (TextDocumentIdentifier -> Session ()) -> TestTree -goldenWithRename title path = - goldenWithHaskellDoc renamePlugin title testDataDir path "expected" "hs" +goldenWithRename :: TestName-> FilePath -> (TextDocumentIdentifier -> Session ()) -> TestTree +goldenWithRename title path act = + goldenWithHaskellDoc renamePlugin title testDataDir path "expected" "hs" $ \doc -> do + sendConfigurationChanged $ toJSON $ + def { plugins = M.fromList [("rename", def { plcConfig = "crossModule" .= True })] } + act doc + testDataDir :: FilePath testDataDir = "test" "testdata" From f35775e7d74a1d35e66e193af55bd07df696124b Mon Sep 17 00:00:00 2001 From: Oliver Madine <30090176+OliverMadine@users.noreply.github.com> Date: Sat, 2 Apr 2022 19:58:56 +0100 Subject: [PATCH 13/20] update docs for cross-module renaming --- docs/configuration.md | 4 +++- docs/features.md | 4 ++-- docs/supported-versions.md | 1 + 3 files changed, 6 insertions(+), 3 deletions(-) diff --git a/docs/configuration.md b/docs/configuration.md index 5b37f6c290..e91bf55532 100644 --- a/docs/configuration.md +++ b/docs/configuration.md @@ -50,7 +50,7 @@ Here is a list of the additional settings currently supported by `haskell-langua Plugins have a generic config to control their behaviour. The schema of such config is: - `haskell.plugin.${pluginName}.globalOn`: usually with default true. Whether the plugin is enabled at runtime or it is not. That is the option you might use if you want to disable completely a plugin. - - Actual plugin names are: `ghcide-code-actions-fill-holes`, `ghcide-completions`, `ghcide-hover-and-symbols`, `ghcide-type-lenses`, `ghcide-code-actions-type-signatures`, `ghcide-code-actions-bindings`, `ghcide-code-actions-imports-exports`, `eval`, `moduleName`, `pragmas`, `refineImports`, `importLens`, `class`, `tactics` (aka wingman), `hlint`, `haddockComments`, `retrie`, `splice`. + - Actual plugin names are: `ghcide-code-actions-fill-holes`, `ghcide-completions`, `ghcide-hover-and-symbols`, `ghcide-type-lenses`, `ghcide-code-actions-type-signatures`, `ghcide-code-actions-bindings`, `ghcide-code-actions-imports-exports`, `eval`, `moduleName`, `pragmas`, `refineImports`, `importLens`, `class`, `tactics` (aka wingman), `hlint`, `haddockComments`, `retrie`, `rename`, `splice`. - So to disable the import lens with an explicit list of module definitions you could set `haskell.plugin.importLens.globalOn: false` - `haskell.plugin.${pluginName}.${lspCapability}On`: usually with default true. Whether a concrete plugin capability is enabled. - Capabilities are the different ways a lsp server can interact with the editor. The current available capabilities of the server are: `callHierarchy`, `codeActions`, `codeLens`, `diagnostics`, `hover`, `symbols`, `completion`, `rename`. @@ -66,6 +66,8 @@ Plugins have a generic config to control their behaviour. The schema of such con - `eval`: - `haskell.plugin.eval.config.diff`, default true: When reloading haddock test results in changes, mark it with WAS/NOW. - `haskell.plugin.eval.config.exception`, default false: When the command results in an exception, mark it with `*** Exception:`. + - `rename`: + - `haskell.plugin.rename.config.diff`, default false: Enables renaming across modules (experimental) - `ghcide-completions`: - `haskell.plugin.ghcide-completions.config.snippetsOn`, default true: Inserts snippets when using code completions. - `haskell.plugin.ghcide-completions.config.autoExtendOn`, default true: Extends the import list automatically when completing a out-of-scope identifier. diff --git a/docs/features.md b/docs/features.md index 77522fb322..8b2faeff4e 100644 --- a/docs/features.md +++ b/docs/features.md @@ -310,13 +310,13 @@ support. Provided by: `hls-rename-plugin` -Provides renaming of symbols within a module. +Provides renaming of symbols within a module. Experimental cross-module renaming can be enabled via the configuration. ![Rename Demo](https://user-images.githubusercontent.com/30090176/133072143-d7d03ec7-3db1-474e-ad5e-6f40d75ff7ab.gif) Known limitations: -- Only works within a module due to limited [multi-component support](https://github.com/haskell/haskell-language-server/issues/2193). +- Cross-module renaming requires all components to be indexed, which sometimes causes [partial renames in multi-component projects.](https://github.com/haskell/haskell-language-server/issues/2193). ## Missing features diff --git a/docs/supported-versions.md b/docs/supported-versions.md index 7094fdc023..1376d5b382 100644 --- a/docs/supported-versions.md +++ b/docs/supported-versions.md @@ -49,6 +49,7 @@ Sometimes a plugin will be supported in the prebuilt binaries but not in a HLS b | `hls-pragmas-plugin` | | | `hls-qualify-imported-names-plugin` | | | `hls-refine-imports-plugin` | | +| `hls-rename-plugin` | | | `hls-retrie-plugin` | 9.2 | | `hls-splice-plugin` | 9.2 | | `hls-stylish-haskell-plugin` | 9.0, 9.2 | From b6065ca2002a75c30eca3dc269e1d46339a8d4ab Mon Sep 17 00:00:00 2001 From: Oliver Madine <30090176+OliverMadine@users.noreply.github.com> Date: Sat, 2 Apr 2022 22:15:21 +0100 Subject: [PATCH 14/20] fix within module renaming for ghc-9 --- plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs b/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs index 4404f94c23..0993b18b63 100644 --- a/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs +++ b/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs @@ -239,7 +239,7 @@ unsafeSrcSpanToLoc srcSpan = replaceModName :: Name -> Maybe ModuleName -> Module replaceModName name mbModName = - mkModule (moduleUnitId $ nameModule name) (fromMaybe (mkModuleName "Main") mbModName) + mkModule (moduleUnit $ nameModule name) (fromMaybe (mkModuleName "Main") mbModName) --------------------------------------------------------------------------------------------------- -- Config From 61656f54ea9b315216dbd615ee62d717b8e1431c Mon Sep 17 00:00:00 2001 From: Oliver Madine <30090176+OliverMadine@users.noreply.github.com> Date: Sat, 2 Apr 2022 22:52:50 +0100 Subject: [PATCH 15/20] fix rename plugin language extensions for ghc-92 --- plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs b/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs index 0993b18b63..118e9683d1 100644 --- a/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs +++ b/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs @@ -7,6 +7,7 @@ {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE TypeApplications #-} module Ide.Plugin.Rename (descriptor) where From 53b9cee5facfdf8d37bb7604b9751e5063e23b98 Mon Sep 17 00:00:00 2001 From: Oliver Madine <30090176+OliverMadine@users.noreply.github.com> Date: Sat, 2 Apr 2022 23:53:55 +0100 Subject: [PATCH 16/20] add explicit GHC.Parser imports in rename plugin --- plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs b/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs index 118e9683d1..706c3a9e5e 100644 --- a/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs +++ b/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs @@ -12,7 +12,7 @@ module Ide.Plugin.Rename (descriptor) where #if MIN_VERSION_ghc(9,2,1) -import GHC.Parser.Annotation +import GHC.Parser.Annotation (AnnContext, AnnList, AnnParen, AnnPragma) #endif import Control.Monad From d024a6bb2747e30a2429e428eb90489deebee675 Mon Sep 17 00:00:00 2001 From: Oliver Madine <30090176+OliverMadine@users.noreply.github.com> Date: Sun, 3 Apr 2022 13:23:51 +0100 Subject: [PATCH 17/20] fix typo in rename docs --- docs/features.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/docs/features.md b/docs/features.md index 8b2faeff4e..74a686b8cd 100644 --- a/docs/features.md +++ b/docs/features.md @@ -316,7 +316,7 @@ Provides renaming of symbols within a module. Experimental cross-module renaming Known limitations: -- Cross-module renaming requires all components to be indexed, which sometimes causes [partial renames in multi-component projects.](https://github.com/haskell/haskell-language-server/issues/2193). +- Cross-module renaming requires all components to be indexed, which sometimes causes [partial renames in multi-component projects](https://github.com/haskell/haskell-language-server/issues/2193). ## Missing features From b469eefd9758e65c72dd432cd59355ab887b5f71 Mon Sep 17 00:00:00 2001 From: Oliver Madine <30090176+OliverMadine@users.noreply.github.com> Date: Sun, 3 Apr 2022 13:24:17 +0100 Subject: [PATCH 18/20] use implicit import lists in rename plugin --- plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs b/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs index 706c3a9e5e..16273d268b 100644 --- a/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs +++ b/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs @@ -23,7 +23,7 @@ import Data.Generics import Data.HashSet (HashSet) import qualified Data.HashSet as HS import Data.Hashable -import Data.List.Extra (foldl', groupOn) +import Data.List.Extra import qualified Data.Map as M import Data.Maybe import Data.Mod.Word From bb91db031e7c1962084d9c69aa3761e2cd118b97 Mon Sep 17 00:00:00 2001 From: Oliver Madine <30090176+OliverMadine@users.noreply.github.com> Date: Sun, 3 Apr 2022 18:20:34 +0100 Subject: [PATCH 19/20] relocate orphaned instances from rename plugin --- ghcide/ghcide.cabal | 1 + ghcide/src/Development/IDE/GHC/Orphans.hs | 9 +++++++++ plugins/hls-rename-plugin/hls-rename-plugin.cabal | 1 - plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs | 7 ------- 4 files changed, 10 insertions(+), 8 deletions(-) diff --git a/ghcide/ghcide.cabal b/ghcide/ghcide.cabal index b34170e68c..6a28edd2c3 100644 --- a/ghcide/ghcide.cabal +++ b/ghcide/ghcide.cabal @@ -66,6 +66,7 @@ library hiedb == 0.4.1.*, lsp-types ^>= 1.4.0.1, lsp ^>= 1.4.0.0 , + mod, monoid-subclasses, mtl, network-uri, diff --git a/ghcide/src/Development/IDE/GHC/Orphans.hs b/ghcide/src/Development/IDE/GHC/Orphans.hs index 4eae21c2a3..f738cd1092 100644 --- a/ghcide/src/Development/IDE/GHC/Orphans.hs +++ b/ghcide/src/Development/IDE/GHC/Orphans.hs @@ -33,11 +33,13 @@ import Retrie.ExactPrint (Annotated) import Development.IDE.GHC.Compat import Development.IDE.GHC.Util +import Development.IDE.Types.Location import Control.DeepSeq import Data.Aeson import Data.Bifunctor (Bifunctor (..)) import Data.Hashable +import Data.Mod.Word import Data.String (IsString (fromString)) #if MIN_VERSION_ghc(9,0,0) import GHC.ByteCode.Types @@ -45,6 +47,8 @@ import GHC.ByteCode.Types import ByteCodeTypes #endif +import Language.LSP.Types (UInt) + -- Orphan instances for types from the GHC API. instance Show CoreModule where show = prettyPrint instance NFData CoreModule where rnf = rwhnf @@ -139,6 +143,11 @@ instance Show ModuleName where instance Hashable ModuleName where hashWithSalt salt = hashWithSalt salt . show +instance Hashable Location +instance Hashable Range +instance Hashable Position +instance Hashable UInt +instance Hashable (Mod a) where hash n = hash (unMod n) instance NFData a => NFData (IdentifierDetails a) where rnf (IdentifierDetails a b) = rnf a `seq` rnf (length b) diff --git a/plugins/hls-rename-plugin/hls-rename-plugin.cabal b/plugins/hls-rename-plugin/hls-rename-plugin.cabal index 9b6b7576e9..92e66718c0 100644 --- a/plugins/hls-rename-plugin/hls-rename-plugin.cabal +++ b/plugins/hls-rename-plugin/hls-rename-plugin.cabal @@ -31,7 +31,6 @@ library , hls-plugin-api ^>=1.3 , lsp , lsp-types - , mod , syb , text , transformers diff --git a/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs b/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs index 16273d268b..590753404c 100644 --- a/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs +++ b/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs @@ -26,7 +26,6 @@ import Data.Hashable import Data.List.Extra import qualified Data.Map as M import Data.Maybe -import Data.Mod.Word import qualified Data.Text as T import Development.IDE.Core.PositionMapping import Development.IDE.Core.RuleTypes @@ -48,12 +47,6 @@ import Ide.Types import Language.LSP.Server import Language.LSP.Types -instance Hashable Location -instance Hashable Range -instance Hashable Position -instance Hashable UInt -instance Hashable (Mod a) where hash n = hash (unMod n) - descriptor :: PluginId -> PluginDescriptor IdeState descriptor pluginId = (defaultPluginDescriptor pluginId) { pluginHandlers = mkPluginHandler STextDocumentRename renameProvider From 70f4e188b0b3ca8f827780ca01cda67f11100b6f Mon Sep 17 00:00:00 2001 From: Oliver Madine <30090176+OliverMadine@users.noreply.github.com> Date: Sun, 3 Apr 2022 20:36:23 +0100 Subject: [PATCH 20/20] Revert "relocate orphaned instances from rename plugin" This reverts commit bb91db031e7c1962084d9c69aa3761e2cd118b97. --- ghcide/ghcide.cabal | 1 - ghcide/src/Development/IDE/GHC/Orphans.hs | 9 --------- plugins/hls-rename-plugin/hls-rename-plugin.cabal | 1 + plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs | 7 +++++++ 4 files changed, 8 insertions(+), 10 deletions(-) diff --git a/ghcide/ghcide.cabal b/ghcide/ghcide.cabal index 6a28edd2c3..b34170e68c 100644 --- a/ghcide/ghcide.cabal +++ b/ghcide/ghcide.cabal @@ -66,7 +66,6 @@ library hiedb == 0.4.1.*, lsp-types ^>= 1.4.0.1, lsp ^>= 1.4.0.0 , - mod, monoid-subclasses, mtl, network-uri, diff --git a/ghcide/src/Development/IDE/GHC/Orphans.hs b/ghcide/src/Development/IDE/GHC/Orphans.hs index f738cd1092..4eae21c2a3 100644 --- a/ghcide/src/Development/IDE/GHC/Orphans.hs +++ b/ghcide/src/Development/IDE/GHC/Orphans.hs @@ -33,13 +33,11 @@ import Retrie.ExactPrint (Annotated) import Development.IDE.GHC.Compat import Development.IDE.GHC.Util -import Development.IDE.Types.Location import Control.DeepSeq import Data.Aeson import Data.Bifunctor (Bifunctor (..)) import Data.Hashable -import Data.Mod.Word import Data.String (IsString (fromString)) #if MIN_VERSION_ghc(9,0,0) import GHC.ByteCode.Types @@ -47,8 +45,6 @@ import GHC.ByteCode.Types import ByteCodeTypes #endif -import Language.LSP.Types (UInt) - -- Orphan instances for types from the GHC API. instance Show CoreModule where show = prettyPrint instance NFData CoreModule where rnf = rwhnf @@ -143,11 +139,6 @@ instance Show ModuleName where instance Hashable ModuleName where hashWithSalt salt = hashWithSalt salt . show -instance Hashable Location -instance Hashable Range -instance Hashable Position -instance Hashable UInt -instance Hashable (Mod a) where hash n = hash (unMod n) instance NFData a => NFData (IdentifierDetails a) where rnf (IdentifierDetails a b) = rnf a `seq` rnf (length b) diff --git a/plugins/hls-rename-plugin/hls-rename-plugin.cabal b/plugins/hls-rename-plugin/hls-rename-plugin.cabal index 92e66718c0..9b6b7576e9 100644 --- a/plugins/hls-rename-plugin/hls-rename-plugin.cabal +++ b/plugins/hls-rename-plugin/hls-rename-plugin.cabal @@ -31,6 +31,7 @@ library , hls-plugin-api ^>=1.3 , lsp , lsp-types + , mod , syb , text , transformers diff --git a/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs b/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs index 590753404c..16273d268b 100644 --- a/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs +++ b/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs @@ -26,6 +26,7 @@ import Data.Hashable import Data.List.Extra import qualified Data.Map as M import Data.Maybe +import Data.Mod.Word import qualified Data.Text as T import Development.IDE.Core.PositionMapping import Development.IDE.Core.RuleTypes @@ -47,6 +48,12 @@ import Ide.Types import Language.LSP.Server import Language.LSP.Types +instance Hashable Location +instance Hashable Range +instance Hashable Position +instance Hashable UInt +instance Hashable (Mod a) where hash n = hash (unMod n) + descriptor :: PluginId -> PluginDescriptor IdeState descriptor pluginId = (defaultPluginDescriptor pluginId) { pluginHandlers = mkPluginHandler STextDocumentRename renameProvider