Skip to content

Commit 5eb0ca9

Browse files
authored
Merge pull request #10 from alanz/plugins-play
Add CodeLens example
2 parents 5039cdb + 5403dc8 commit 5eb0ca9

File tree

2 files changed

+55
-3
lines changed

2 files changed

+55
-3
lines changed

ghcide

src/Ide/Plugin/Example.hs

Lines changed: 54 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
{-# LANGUAGE ViewPatterns #-}
12
{-# LANGUAGE DeriveGeneric #-}
23
{-# LANGUAGE DuplicateRecordFields #-}
34
{-# LANGUAGE FlexibleContexts #-}
@@ -13,6 +14,8 @@ module Ide.Plugin.Example
1314
) where
1415

1516
import Control.DeepSeq ( NFData )
17+
import Control.Monad.Trans.Maybe
18+
import Data.Aeson.Types (toJSON, fromJSON, Value(..), Result(..))
1619
import Data.Binary
1720
import Data.Functor
1821
import qualified Data.HashMap.Strict as Map
@@ -22,6 +25,7 @@ import qualified Data.Text as T
2225
import Data.Typeable
2326
import Development.IDE.Core.OfInterest
2427
import Development.IDE.Core.Rules
28+
import Development.IDE.Core.RuleTypes
2529
import Development.IDE.Core.Service
2630
import Development.IDE.Core.Shake
2731
import Development.IDE.LSP.Server
@@ -39,7 +43,9 @@ import Text.Regex.TDFA.Text()
3943
-- ---------------------------------------------------------------------
4044

4145
plugin :: Plugin
42-
plugin = Plugin exampleRules handlersExample <> codeActionPlugin codeAction
46+
plugin = Plugin exampleRules handlersExample
47+
<> codeActionPlugin codeAction
48+
<> Plugin mempty handlersCodeLens
4349

4450
hover :: IdeState -> TextDocumentPositionParams -> IO (Maybe Hover)
4551
hover = request "Hover" blah Nothing foundHover
@@ -103,11 +109,57 @@ codeAction
103109
codeAction _lsp _state (TextDocumentIdentifier uri) _range CodeActionContext{_diagnostics=List _xs} = do
104110
let
105111
title = "Add TODO Item"
106-
tedit = [TextEdit (Range (Position 0 0) (Position 1 0)) "-- TODO added by Example Plugin directly\n"]
112+
tedit = [TextEdit (Range (Position 0 0) (Position 0 0))
113+
"-- TODO added by Example Plugin directly\n"]
107114
edit = WorkspaceEdit (Just $ Map.singleton uri $ List tedit) Nothing
108115
pure
109116
[ CACodeAction $ CodeAction title (Just CodeActionQuickFix) (Just $ List []) (Just edit) Nothing ]
110117

118+
-- ---------------------------------------------------------------------
119+
120+
-- | Generate code lenses.
121+
handlersCodeLens :: PartialHandlers
122+
handlersCodeLens = PartialHandlers $ \WithMessage{..} x -> return x{
123+
LSP.codeLensHandler = withResponse RspCodeLens codeLens,
124+
LSP.executeCommandHandler = withResponseAndRequest RspExecuteCommand ReqApplyWorkspaceEdit executeAddSignatureCommand
125+
}
126+
127+
codeLens
128+
:: LSP.LspFuncs ()
129+
-> IdeState
130+
-> CodeLensParams
131+
-> IO (List CodeLens)
132+
codeLens _lsp ideState CodeLensParams{_textDocument=TextDocumentIdentifier uri} = do
133+
case uriToFilePath' uri of
134+
Just (toNormalizedFilePath -> filePath) -> do
135+
_ <- runAction ideState $ runMaybeT $ useE TypeCheck filePath
136+
_diag <- getDiagnostics ideState
137+
_hDiag <- getHiddenDiagnostics ideState
138+
let
139+
title = "Add TODO Item via Code Lens"
140+
tedit = [TextEdit (Range (Position 3 0) (Position 3 0))
141+
"-- TODO added by Example Plugin via code lens action\n"]
142+
edit = WorkspaceEdit (Just $ Map.singleton uri $ List tedit) Nothing
143+
range = (Range (Position 3 0) (Position 4 0))
144+
pure $ List
145+
-- [ CodeLens range (Just (Command title "codelens.do" (Just $ List [toJSON edit]))) Nothing
146+
[ CodeLens range (Just (Command title "codelens.todo" (Just $ List [toJSON edit]))) Nothing
147+
]
148+
Nothing -> pure $ List []
149+
150+
-- | Execute the "codelens.todo" command.
151+
executeAddSignatureCommand
152+
:: LSP.LspFuncs ()
153+
-> IdeState
154+
-> ExecuteCommandParams
155+
-> IO (Value, Maybe (ServerMethod, ApplyWorkspaceEditParams))
156+
executeAddSignatureCommand _lsp _ideState ExecuteCommandParams{..}
157+
| _command == "codelens.todo"
158+
, Just (List [edit]) <- _arguments
159+
, Success wedit <- fromJSON edit
160+
= return (Null, Just (WorkspaceApplyEdit, ApplyWorkspaceEditParams wedit))
161+
| otherwise
162+
= return (Null, Nothing)
111163

112164
-- ---------------------------------------------------------------------
113165

0 commit comments

Comments
 (0)