1
1
{-# LANGUAGE ViewPatterns #-}
2
+ {-# LANGUAGE DeriveAnyClass #-}
2
3
{-# LANGUAGE DeriveGeneric #-}
3
4
{-# LANGUAGE DuplicateRecordFields #-}
4
5
{-# LANGUAGE FlexibleContexts #-}
5
6
{-# LANGUAGE FlexibleInstances #-}
6
7
{-# LANGUAGE OverloadedStrings #-}
7
- {-# LANGUAGE RecordWildCards #-}
8
8
{-# LANGUAGE TupleSections #-}
9
9
{-# LANGUAGE TypeFamilies #-}
10
10
@@ -15,25 +15,26 @@ module Ide.Plugin.Example2
15
15
16
16
import Control.DeepSeq ( NFData )
17
17
import Control.Monad.Trans.Maybe
18
- import Data.Aeson.Types ( toJSON )
18
+ import Data.Aeson
19
19
import Data.Binary
20
20
import Data.Functor
21
21
import qualified Data.HashMap.Strict as Map
22
- import Data.Hashable
23
22
import qualified Data.HashSet as HashSet
23
+ import Data.Hashable
24
24
import qualified Data.Text as T
25
25
import Data.Typeable
26
26
import Development.IDE.Core.OfInterest
27
- import Development.IDE.Core.Rules
28
27
import Development.IDE.Core.RuleTypes
28
+ import Development.IDE.Core.Rules
29
29
import Development.IDE.Core.Service
30
30
import Development.IDE.Core.Shake
31
31
import Development.IDE.Types.Diagnostics as D
32
32
import Development.IDE.Types.Location
33
33
import Development.IDE.Types.Logger
34
34
import Development.Shake hiding ( Diagnostic )
35
- import Ide.Types
36
35
import GHC.Generics
36
+ import Ide.Plugin
37
+ import Ide.Types
37
38
import Language.Haskell.LSP.Types
38
39
import Text.Regex.TDFA.Text ()
39
40
@@ -43,12 +44,12 @@ descriptor :: PluginId -> PluginDescriptor
43
44
descriptor plId = PluginDescriptor
44
45
{ pluginId = plId
45
46
, pluginRules = exampleRules
46
- , pluginCommands = []
47
+ , pluginCommands = [PluginCommand " codelens.todo " " example adding " addTodoCmd ]
47
48
, pluginCodeActionProvider = Just codeAction
48
49
, pluginCodeLensProvider = Just codeLens
49
50
, pluginDiagnosticProvider = Nothing
50
- , pluginHoverProvider = Just hover
51
- , pluginSymbolProvider = Nothing
51
+ , pluginHoverProvider = Just hover
52
+ , pluginSymbolProvider = Nothing
52
53
, pluginFormattingProvider = Nothing
53
54
, pluginCompletionProvider = Nothing
54
55
}
@@ -63,6 +64,8 @@ blah _ (Position line col)
63
64
= return $ Just (Just (Range (Position line col) (Position (line+ 1 ) 0 )), [" example hover 2\n " ])
64
65
65
66
-- ---------------------------------------------------------------------
67
+ -- Generating Diagnostics via rules
68
+ -- ---------------------------------------------------------------------
66
69
67
70
data Example2 = Example2
68
71
deriving (Eq , Show , Typeable , Generic )
@@ -100,6 +103,8 @@ mkDiag file diagSource sev loc msg = (file, D.ShowDiag,)
100
103
}
101
104
102
105
-- ---------------------------------------------------------------------
106
+ -- code actions
107
+ -- ---------------------------------------------------------------------
103
108
104
109
-- | Generate code actions.
105
110
codeAction
@@ -125,24 +130,43 @@ codeLens
125
130
-> PluginId
126
131
-> CodeLensParams
127
132
-> IO (Either ResponseError (List CodeLens ))
128
- codeLens ideState _plId CodeLensParams {_textDocument= TextDocumentIdentifier uri} =
133
+ codeLens ideState plId CodeLensParams {_textDocument= TextDocumentIdentifier uri} = do
134
+ logInfo (ideLogger ideState) " Example2.codeLens entered (ideLogger)" -- AZ
129
135
case uriToFilePath' uri of
130
136
Just (toNormalizedFilePath -> filePath) -> do
131
137
_ <- runAction ideState $ runMaybeT $ useE TypeCheck filePath
132
138
_diag <- getDiagnostics ideState
133
139
_hDiag <- getHiddenDiagnostics ideState
134
140
let
135
141
title = " Add TODO2 Item via Code Lens"
136
- tedit = [TextEdit (Range (Position 3 0 ) (Position 3 0 ))
137
- " -- TODO2 added by Example2 Plugin via code lens action\n " ]
138
- edit = WorkspaceEdit (Just $ Map. singleton uri $ List tedit) Nothing
139
142
range = Range (Position 3 0 ) (Position 4 0 )
140
- pure $ Right $ List
141
- -- [ CodeLens range (Just (Command title "codelens.do" (Just $ List [toJSON edit]))) Nothing
142
- [ CodeLens range (Just (Command title " codelens.todo" (Just $ List [toJSON edit]))) Nothing
143
- ]
143
+ let cmdParams = AddTodoParams uri " do abc"
144
+ cmd <- mkLspCommand plId " codelens.todo" title (Just [toJSON cmdParams])
145
+ pure $ Right $ List [ CodeLens range (Just cmd) Nothing ]
144
146
Nothing -> pure $ Right $ List []
145
147
148
+ -- ---------------------------------------------------------------------
149
+ -- | Parameters for the addTodo PluginCommand.
150
+ data AddTodoParams = AddTodoParams
151
+ { file :: Uri -- ^ Uri of the file to add the pragma to
152
+ , todoText :: T. Text
153
+ }
154
+ deriving (Show , Eq , Generic , ToJSON , FromJSON )
155
+
156
+ addTodoCmd :: AddTodoParams -> IO (Either ResponseError Value ,
157
+ Maybe (ServerMethod , ApplyWorkspaceEditParams ))
158
+ addTodoCmd (AddTodoParams uri todoText) = do
159
+ let
160
+ pos = Position 0 0
161
+ textEdits = List
162
+ [TextEdit (Range pos pos)
163
+ (" -- TODO2:" <> todoText <> " \n " )
164
+ ]
165
+ res = WorkspaceEdit
166
+ (Just $ Map. singleton uri textEdits)
167
+ Nothing
168
+ return (Right Null , Just (WorkspaceApplyEdit , ApplyWorkspaceEditParams res))
169
+
146
170
-- ---------------------------------------------------------------------
147
171
148
172
foundHover :: (Maybe Range , [T. Text ]) -> Either ResponseError (Maybe Hover )
@@ -166,7 +190,8 @@ request label getResults notFound found ide (TextDocumentPositionParams (TextDoc
166
190
Nothing -> pure Nothing
167
191
pure $ maybe notFound found mbResult
168
192
169
- logAndRunRequest :: T. Text -> (NormalizedFilePath -> Position -> Action b ) -> IdeState -> Position -> String -> IO b
193
+ logAndRunRequest :: T. Text -> (NormalizedFilePath -> Position -> Action b )
194
+ -> IdeState -> Position -> String -> IO b
170
195
logAndRunRequest label getResults ide pos path = do
171
196
let filePath = toNormalizedFilePath path
172
197
logInfo (ideLogger ide) $
0 commit comments