1
1
{-# LANGUAGE GADTs #-}
2
2
{-# LANGUAGE OverloadedLists #-}
3
3
{-# LANGUAGE RecordWildCards #-}
4
- {-# LANGUAGE CPP #-}
5
4
{-# OPTIONS_GHC -Wno-overlapping -patterns #-}
6
5
7
6
module Ide.Plugin.Class.CodeLens where
8
7
9
- import Control.Lens ((^.) )
10
- import Control.Monad.IO.Class (liftIO )
8
+ import Control.Lens ((^.) )
9
+ import Control.Monad.IO.Class (liftIO )
11
10
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
14
13
import Development.IDE
14
+ import Development.IDE.Core.PositionMapping
15
15
import Development.IDE.GHC.Compat
16
16
import Development.IDE.GHC.Compat.Util
17
17
import GHC.LanguageExtensions.Type
18
18
import Ide.Plugin.Class.Types
19
19
import Ide.Plugin.Class.Utils
20
20
import Ide.PluginUtils
21
21
import Ide.Types
22
- import Language.LSP.Server (sendRequest )
22
+ import Language.LSP.Server (sendRequest )
23
23
import Language.LSP.Types
24
- import qualified Language.LSP.Types.Lens as J
24
+ import qualified Language.LSP.Types.Lens as J
25
25
26
26
codeLens :: PluginMethodHandler IdeState TextDocumentCodeLens
27
27
codeLens state plId CodeLensParams {.. } = pluginResponse $ do
28
28
nfp <- getNormalizedFilePath uri
29
- tmr <- handleMaybeM " Unable to typecheck"
29
+ ( tmr, _) <- handleMaybeM " Unable to typecheck"
30
30
$ liftIO
31
31
$ 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
33
35
34
36
-- All instance binds
35
- InstanceBindTypeSigsResult allBinds <-
37
+ ( InstanceBindTypeSigsResult allBinds, mp) <-
36
38
handleMaybeM " Unable to get InstanceBindTypeSigsResult"
37
39
$ liftIO
38
40
$ 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
40
44
41
45
pragmaInsertion <- insertPragmaIfNotPresent state nfp InstanceSigs
42
46
@@ -53,7 +57,7 @@ codeLens state plId CodeLensParams{..} = pluginResponse $ do
53
57
makeLens (range, title) =
54
58
generateLens plId range title
55
59
$ workspaceEdit pragmaInsertion
56
- $ makeEdit range title
60
+ $ makeEdit range title mp
57
61
codeLens = makeLens <$> mapMaybe getRangeWithSig targetSigs
58
62
59
63
pure $ List codeLens
@@ -97,13 +101,9 @@ codeLens state plId CodeLensParams{..} = pluginResponse $ do
97
101
-- that are nonsense for displaying code lenses.
98
102
--
99
103
-- 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
107
107
-- Existed signatures' name
108
108
sigNames = concat $ mapMaybe (\ (L _ r) -> getSigName r) cid_sigs
109
109
toBindInfo (L l (L l' _)) = BindInfo
@@ -130,12 +130,14 @@ codeLens state plId CodeLensParams{..} = pluginResponse $ do
130
130
let cmd = mkLspCommand plId typeLensCommandId title (Just [toJSON edit])
131
131
in CodeLens range (Just cmd) Nothing
132
132
133
- makeEdit :: Range -> T. Text -> [TextEdit ]
134
- makeEdit range bind =
133
+ makeEdit :: Range -> T. Text -> PositionMapping -> [TextEdit ]
134
+ makeEdit range bind mp =
135
135
let startPos = range ^. J. start
136
136
insertChar = startPos ^. J. character
137
137
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 -> []
139
141
140
142
codeLensCommandHandler :: CommandFunction IdeState WorkspaceEdit
141
143
codeLensCommandHandler _ wedit = do
0 commit comments