8
8
{-# LANGUAGE RankNTypes #-}
9
9
{-# LANGUAGE ScopedTypeVariables #-}
10
10
{-# LANGUAGE TypeApplications #-}
11
+ {-# LANGUAGE RecordWildCards #-}
11
12
12
13
module Ide.Plugin.Rename (descriptor , E. Log ) where
13
14
@@ -21,11 +22,13 @@ import Control.Monad.IO.Class
21
22
import Control.Monad.Trans.Class
22
23
import Control.Monad.Trans.Except
23
24
import Data.Generics
25
+ import Data.Bifunctor (first )
24
26
import Data.Hashable
25
27
import Data.HashSet (HashSet )
26
28
import qualified Data.HashSet as HS
27
29
import Data.List.Extra hiding (length )
28
30
import qualified Data.Map as M
31
+ import qualified Data.Set as S
29
32
import Data.Maybe
30
33
import Data.Mod.Word
31
34
import qualified Data.Text as T
@@ -51,6 +54,7 @@ import Ide.PluginUtils
51
54
import Ide.Types
52
55
import Language.LSP.Server
53
56
import Language.LSP.Types
57
+ import Compat.HieTypes
54
58
55
59
instance Hashable (Mod a ) where hash n = hash (unMod n)
56
60
@@ -74,7 +78,10 @@ renameProvider state pluginId (RenameParams (TextDocumentIdentifier uri) pos _pr
74
78
See the `IndirectPuns` test for an example. -}
75
79
indirectOldNames <- concat . filter ((> 1 ) . Prelude. length ) <$>
76
80
mapM (uncurry (getNamesAtPos state) . locToFilePos) directRefs
77
- let oldNames = indirectOldNames ++ directOldNames
81
+ let oldNames = (filter matchesDirect indirectOldNames) ++ directOldNames
82
+ matchesDirect n = occNameFS (nameOccName n) `elem` directFS
83
+ where
84
+ directFS = map (occNameFS. nameOccName) directOldNames
78
85
refs <- HS. fromList . concat <$> mapM (refsAtName state nfp) oldNames
79
86
80
87
-- Validate rename
@@ -220,7 +227,21 @@ handleGetHieAst ::
220
227
ExceptT String m (HieAstResult , PositionMapping )
221
228
handleGetHieAst state nfp = handleMaybeM
222
229
(" No AST for file: " ++ show nfp)
223
- (liftIO $ runAction " Rename.GetHieAst" state $ useWithStale GetHieAst nfp)
230
+ (liftIO $ fmap (fmap (first removeGenerated)) $ runAction " Rename.GetHieAst" state $ useWithStale GetHieAst nfp)
231
+
232
+ -- | We don't want to rename in code generated by GHC as this gives false positives.
233
+ -- So we restrict the HIE file to remove all the generated code.
234
+ removeGenerated :: HieAstResult -> HieAstResult
235
+ removeGenerated HAR {.. } = HAR {hieAst = go hieAst,.. }
236
+ where
237
+ go :: HieASTs a -> HieASTs a
238
+ go hf =
239
+ #if MIN_VERSION_ghc(9,2,1)
240
+ HieASTs (fmap goAst (getAsts hf))
241
+ goAst (Node nsi sp xs) = Node (SourcedNodeInfo $ M. restrictKeys (getSourcedNodeInfo nsi) (S. singleton SourceInfo )) sp (map goAst xs)
242
+ #else
243
+ hf
244
+ #endif
224
245
225
246
handleUriToNfp :: (Monad m ) => Uri -> ExceptT String m NormalizedFilePath
226
247
handleUriToNfp uri = handleMaybe
0 commit comments