Skip to content

Commit 1b8ce5f

Browse files
committed
Add CodeLens based dependency version
1 parent 69d5fbf commit 1b8ce5f

File tree

2 files changed

+29
-4
lines changed

2 files changed

+29
-4
lines changed

plugins/hls-cabal-plugin/src/Ide/Plugin/Cabal.hs

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -138,6 +138,7 @@ descriptor recorder plId =
138138
, mkPluginHandler LSP.SMethod_TextDocumentDefinition gotoDefinition
139139
, mkPluginHandler LSP.SMethod_TextDocumentHover hover
140140
, mkPluginHandler LSP.SMethod_TextDocumentInlayHint hints
141+
, mkPluginHandler LSP.SMethod_TextDocumentCodeLens lens
141142
]
142143
, pluginNotificationHandlers =
143144
mconcat
@@ -379,6 +380,15 @@ cabalAddCodeAction state plId (CodeActionParams _ _ (TextDocumentIdentifier uri)
379380
gpd
380381
pure $ InL $ fmap InR actions
381382

383+
lens :: PluginMethodHandler IdeState LSP.Method_TextDocumentCodeLens
384+
lens state _plId clp = do
385+
let uri = clp ^. JL.textDocument . JL.uri
386+
nfp <- getNormalizedFilePathE uri
387+
cabalFields <- runActionE "cabal.cabal-code-lens" state $ useE ParseCabalFields nfp
388+
(hscEnv -> hsc) <- runActionE "cabal.cabal-code-lens" state $ useE GhcSession nfp
389+
pure $ InL $ Dependencies.dependencyVersionLens cabalFields hsc
390+
391+
382392
hints :: PluginMethodHandler IdeState LSP.Method_TextDocumentInlayHint
383393
hints state _plId clp = do
384394
let uri = clp ^. JL.textDocument . JL.uri

plugins/hls-cabal-plugin/src/Ide/Plugin/Cabal/Dependencies.hs

Lines changed: 19 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,7 @@
1-
{-# LANGUAGE OverloadedStrings #-}
2-
module Ide.Plugin.Cabal.Dependencies (dependencyVersionHints, collectPackageDependencyVersions) where
1+
{-# LANGUAGE DuplicateRecordFields #-}
2+
{-# LANGUAGE OverloadedStrings #-}
3+
4+
module Ide.Plugin.Cabal.Dependencies (dependencyVersionHints, collectPackageDependencyVersions, dependencyVersionLens) where
35

46
import qualified Data.Char as Char
57
import qualified Data.List as List
@@ -15,9 +17,22 @@ import Development.IDE.GHC.Compat (HscEnv, filterUniqMap,
1517
import qualified Distribution.Fields as Syntax
1618
import qualified Distribution.Parsec.Position as Syntax
1719
import qualified Ide.Plugin.Cabal.Completion.Types as Types
18-
import Language.LSP.Protocol.Types (InlayHint (..),
20+
import Language.LSP.Protocol.Types (CodeLens (..), Command (..),
21+
InlayHint (..),
1922
InlayHintLabelPart (InlayHintLabelPart),
20-
type (|?) (..))
23+
Range (..), type (|?) (..))
24+
25+
dependencyVersionLens :: [Syntax.Field Syntax.Position] -> HscEnv -> [CodeLens]
26+
dependencyVersionLens cabalFields = fmap mkCodeLens . collectPackageDependencyVersions cabalFields
27+
where
28+
mkCodeLens :: (Syntax.Position, Version) -> CodeLens
29+
mkCodeLens (pos, dependencyVersion) =
30+
let cPos = Types.cabalPositionToLSPPosition pos
31+
command = Command (printVersion dependencyVersion) mempty Nothing
32+
in CodeLens
33+
{ _range = Range cPos cPos
34+
, _command = Just command
35+
, _data_ = Nothing }
2136

2237
dependencyVersionHints :: [Syntax.Field Syntax.Position] -> HscEnv -> [InlayHint]
2338
dependencyVersionHints cabalFields = fmap mkHint . collectPackageDependencyVersions cabalFields

0 commit comments

Comments
 (0)