Skip to content

Commit 30bcab5

Browse files
authored
Keep instance lenses stable even if parsed results are unavailable (#3545)
* Keep stale class lens * Comment why we use useWithStale * Remove cpp to compat package to make pre-commit happy
1 parent 8fc40fb commit 30bcab5

File tree

5 files changed

+49
-25
lines changed

5 files changed

+49
-25
lines changed

ghcide/src/Development/IDE/GHC/Compat/Core.hs

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -496,6 +496,7 @@ module Development.IDE.GHC.Compat.Core (
496496
# if !MIN_VERSION_ghc(9,5,0)
497497
field_label,
498498
#endif
499+
groupOrigin,
499500
) where
500501

501502
import qualified GHC
@@ -1197,9 +1198,11 @@ type UniqFM k = UniqFM.UniqFM
11971198
mkVisFunTys = mkScaledFunctionTys
11981199
mapLoc :: (a -> b) -> SrcLoc.GenLocated l a -> SrcLoc.GenLocated l b
11991200
mapLoc = fmap
1201+
groupOrigin = mg_ext
12001202
#else
12011203
mapLoc :: (a -> b) -> SrcLoc.GenLocated l a -> SrcLoc.GenLocated l b
12021204
mapLoc = SrcLoc.mapLoc
1205+
groupOrigin = mg_origin
12031206
#endif
12041207

12051208

plugins/hls-class-plugin/src/Ide/Plugin/Class/CodeLens.hs

Lines changed: 24 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -1,42 +1,46 @@
11
{-# LANGUAGE GADTs #-}
22
{-# LANGUAGE OverloadedLists #-}
33
{-# LANGUAGE RecordWildCards #-}
4-
{-# LANGUAGE CPP #-}
54
{-# OPTIONS_GHC -Wno-overlapping-patterns #-}
65

76
module Ide.Plugin.Class.CodeLens where
87

9-
import Control.Lens ((^.))
10-
import Control.Monad.IO.Class (liftIO)
8+
import Control.Lens ((^.))
9+
import Control.Monad.IO.Class (liftIO)
1110
import Data.Aeson
12-
import Data.Maybe (mapMaybe, maybeToList)
13-
import qualified Data.Text as T
11+
import Data.Maybe (mapMaybe, maybeToList)
12+
import qualified Data.Text as T
1413
import Development.IDE
14+
import Development.IDE.Core.PositionMapping
1515
import Development.IDE.GHC.Compat
1616
import Development.IDE.GHC.Compat.Util
1717
import GHC.LanguageExtensions.Type
1818
import Ide.Plugin.Class.Types
1919
import Ide.Plugin.Class.Utils
2020
import Ide.PluginUtils
2121
import Ide.Types
22-
import Language.LSP.Server (sendRequest)
22+
import Language.LSP.Server (sendRequest)
2323
import Language.LSP.Types
24-
import qualified Language.LSP.Types.Lens as J
24+
import qualified Language.LSP.Types.Lens as J
2525

2626
codeLens :: PluginMethodHandler IdeState TextDocumentCodeLens
2727
codeLens state plId CodeLensParams{..} = pluginResponse $ do
2828
nfp <- getNormalizedFilePath uri
29-
tmr <- handleMaybeM "Unable to typecheck"
29+
(tmr, _) <- handleMaybeM "Unable to typecheck"
3030
$ liftIO
3131
$ runAction "classplugin.TypeCheck" state
32-
$ use TypeCheck nfp
32+
-- Using stale results means that we can almost always return a value. In practice
33+
-- this means the lenses don't 'flicker'
34+
$ useWithStale TypeCheck nfp
3335

3436
-- All instance binds
35-
InstanceBindTypeSigsResult allBinds <-
37+
(InstanceBindTypeSigsResult allBinds, mp) <-
3638
handleMaybeM "Unable to get InstanceBindTypeSigsResult"
3739
$ liftIO
3840
$ runAction "classplugin.GetInstanceBindTypeSigs" state
39-
$ use GetInstanceBindTypeSigs nfp
41+
-- Using stale results means that we can almost always return a value. In practice
42+
-- this means the lenses don't 'flicker'
43+
$ useWithStale GetInstanceBindTypeSigs nfp
4044

4145
pragmaInsertion <- insertPragmaIfNotPresent state nfp InstanceSigs
4246

@@ -53,7 +57,7 @@ codeLens state plId CodeLensParams{..} = pluginResponse $ do
5357
makeLens (range, title) =
5458
generateLens plId range title
5559
$ workspaceEdit pragmaInsertion
56-
$ makeEdit range title
60+
$ makeEdit range title mp
5761
codeLens = makeLens <$> mapMaybe getRangeWithSig targetSigs
5862

5963
pure $ List codeLens
@@ -97,13 +101,9 @@ codeLens state plId CodeLensParams{..} = pluginResponse $ do
97101
-- that are nonsense for displaying code lenses.
98102
--
99103
-- See https://github.com/haskell/haskell-language-server/issues/3319
100-
#if MIN_VERSION_ghc(9,5,0)
101-
| not $ isGenerated (mg_ext fun_matches)
102-
#else
103-
| not $ isGenerated (mg_origin fun_matches)
104-
#endif
105-
-> Just $ L l fun_id
106-
_ -> Nothing
104+
| not $ isGenerated (groupOrigin fun_matches)
105+
-> Just $ L l fun_id
106+
_ -> Nothing
107107
-- Existed signatures' name
108108
sigNames = concat $ mapMaybe (\(L _ r) -> getSigName r) cid_sigs
109109
toBindInfo (L l (L l' _)) = BindInfo
@@ -130,12 +130,14 @@ codeLens state plId CodeLensParams{..} = pluginResponse $ do
130130
let cmd = mkLspCommand plId typeLensCommandId title (Just [toJSON edit])
131131
in CodeLens range (Just cmd) Nothing
132132

133-
makeEdit :: Range -> T.Text -> [TextEdit]
134-
makeEdit range bind =
133+
makeEdit :: Range -> T.Text -> PositionMapping -> [TextEdit]
134+
makeEdit range bind mp =
135135
let startPos = range ^. J.start
136136
insertChar = startPos ^. J.character
137137
insertRange = Range startPos startPos
138-
in [TextEdit insertRange (bind <> "\n" <> T.replicate (fromIntegral insertChar) " ")]
138+
in case toCurrentRange mp insertRange of
139+
Just rg -> [TextEdit rg (bind <> "\n" <> T.replicate (fromIntegral insertChar) " ")]
140+
Nothing -> []
139141

140142
codeLensCommandHandler :: CommandFunction IdeState WorkspaceEdit
141143
codeLensCommandHandler _ wedit = do

plugins/hls-class-plugin/src/Ide/Plugin/Class/Utils.hs

Lines changed: 6 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -46,6 +46,10 @@ toMethodName n
4646
| otherwise
4747
= n
4848

49+
-- | Here we use `useWithStale` to compute, Using stale results means that we can almost always return a value.
50+
-- In practice this means the lenses don't 'flicker'.
51+
-- This function is also used in code actions, but it doesn't matter because our actions only work
52+
-- if the module parsed success.
4953
insertPragmaIfNotPresent :: (MonadIO m)
5054
=> IdeState
5155
-> NormalizedFilePath
@@ -59,10 +63,10 @@ insertPragmaIfNotPresent state nfp pragma = do
5963
(_, fileContents) <- liftIO
6064
$ runAction "classplugin.insertPragmaIfNotPresent.GetFileContents" state
6165
$ getFileContents nfp
62-
pm <- handleMaybeM "Unable to GetParsedModuleWithComments"
66+
(pm, _) <- handleMaybeM "Unable to GetParsedModuleWithComments"
6367
$ liftIO
6468
$ runAction "classplugin.insertPragmaIfNotPresent.GetParsedModuleWithComments" state
65-
$ use GetParsedModuleWithComments nfp
69+
$ useWithStale GetParsedModuleWithComments nfp
6670
let exts = getExtensions pm
6771
info = getNextPragmaInfo sessionDynFlags fileContents
6872
pure [insertNewPragma info pragma | pragma `notElem` exts]

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

Lines changed: 11 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -27,7 +27,9 @@ classPlugin = mkPluginTestDescriptor Class.descriptor "class"
2727
tests :: TestTree
2828
tests = testGroup
2929
"class"
30-
[codeActionTests, codeLensTests]
30+
[ codeActionTests
31+
, codeLensTests
32+
]
3133

3234
codeActionTests :: TestTree
3335
codeActionTests = testGroup
@@ -101,6 +103,14 @@ codeLensTests = testGroup
101103
goldenCodeLens "Don't insert pragma while GHC2021 enabled" "CodeLensWithGHC2021" 0
102104
, goldenCodeLens "Qualified name" "Qualified" 0
103105
, goldenCodeLens "Type family" "TypeFamily" 0
106+
, testCase "keep stale lens" $ do
107+
runSessionWithServer classPlugin testDataDir $ do
108+
doc <- openDoc "Stale.hs" "haskell"
109+
oldLens <- getCodeLenses doc
110+
let edit = TextEdit (mkRange 4 11 4 12) "" -- Remove the `_`
111+
_ <- applyEdit doc edit
112+
newLens <- getCodeLenses doc
113+
liftIO $ newLens @?= oldLens
104114
]
105115

106116
_CACodeAction :: Prism' (Command |? CodeAction) CodeAction
Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,5 @@
1+
module Stale where
2+
3+
data A a
4+
instance Functor A where
5+
fmap = _

0 commit comments

Comments
 (0)