1
+ {-# LANGUAGE ViewPatterns #-}
1
2
{-# LANGUAGE DeriveGeneric #-}
2
3
{-# LANGUAGE DuplicateRecordFields #-}
3
4
{-# LANGUAGE FlexibleContexts #-}
@@ -13,6 +14,8 @@ module Ide.Plugin.Example
13
14
) where
14
15
15
16
import Control.DeepSeq ( NFData )
17
+ import Control.Monad.Trans.Maybe
18
+ import Data.Aeson.Types (toJSON , fromJSON , Value (.. ), Result (.. ))
16
19
import Data.Binary
17
20
import Data.Functor
18
21
import qualified Data.HashMap.Strict as Map
@@ -22,6 +25,7 @@ import qualified Data.Text as T
22
25
import Data.Typeable
23
26
import Development.IDE.Core.OfInterest
24
27
import Development.IDE.Core.Rules
28
+ import Development.IDE.Core.RuleTypes
25
29
import Development.IDE.Core.Service
26
30
import Development.IDE.Core.Shake
27
31
import Development.IDE.LSP.Server
@@ -39,7 +43,9 @@ import Text.Regex.TDFA.Text()
39
43
-- ---------------------------------------------------------------------
40
44
41
45
plugin :: Plugin
42
- plugin = Plugin exampleRules handlersExample <> codeActionPlugin codeAction
46
+ plugin = Plugin exampleRules handlersExample
47
+ <> codeActionPlugin codeAction
48
+ <> Plugin mempty handlersCodeLens
43
49
44
50
hover :: IdeState -> TextDocumentPositionParams -> IO (Maybe Hover )
45
51
hover = request " Hover" blah Nothing foundHover
@@ -103,11 +109,57 @@ codeAction
103
109
codeAction _lsp _state (TextDocumentIdentifier uri) _range CodeActionContext {_diagnostics= List _xs} = do
104
110
let
105
111
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 " ]
107
114
edit = WorkspaceEdit (Just $ Map. singleton uri $ List tedit) Nothing
108
115
pure
109
116
[ CACodeAction $ CodeAction title (Just CodeActionQuickFix ) (Just $ List [] ) (Just edit) Nothing ]
110
117
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 )
111
163
112
164
-- ---------------------------------------------------------------------
113
165
0 commit comments