77{-# LANGUAGE OverloadedStrings #-}
88{-# LANGUAGE TupleSections #-}
99{-# LANGUAGE TypeFamilies #-}
10+ {-# LANGUAGE DataKinds #-}
11+ {-# LANGUAGE RecordWildCards #-}
1012
1113module Ide.Plugin.Example
1214 (
@@ -30,25 +32,27 @@ import GHC.Generics
3032import Ide.PluginUtils
3133import Ide.Types
3234import Language.LSP.Types
35+ import Language.LSP.Server
3336import Text.Regex.TDFA.Text ()
37+ import Control.Monad.IO.Class
3438
3539-- ---------------------------------------------------------------------
3640
3741descriptor :: PluginId -> PluginDescriptor IdeState
3842descriptor plId = (defaultPluginDescriptor plId)
3943 { pluginRules = exampleRules
4044 , pluginCommands = [PluginCommand " codelens.todo" " example adding" addTodoCmd]
41- , pluginCodeActionProvider = Just codeAction
42- , pluginCodeLensProvider = Just codeLens
43- , pluginHoverProvider = Just hover
44- , pluginSymbolsProvider = Just symbols
45- , pluginCompletionProvider = Just completion
45+ , pluginHandlers = mkPluginHandler STextDocumentCodeAction codeAction
46+ <> mkPluginHandler STextDocumentCodeLens codeLens
47+ <> mkPluginHandler STextDocumentHover hover
48+ <> mkPluginHandler STextDocumentDocumentSymbol symbols
49+ <> mkPluginHandler STextDocumentCompletion completion
4650 }
4751
4852-- ---------------------------------------------------------------------
4953
50- hover :: IdeState -> TextDocumentPositionParams -> IO ( Either ResponseError ( Maybe Hover ))
51- hover = request " Hover" blah (Right Nothing ) foundHover
54+ hover :: PluginMethodHandler IdeState TextDocumentHover
55+ hover ide _ HoverParams { .. } = liftIO $ request " Hover" blah (Right Nothing ) foundHover ide TextDocumentPositionParams { .. }
5256
5357blah :: NormalizedFilePath -> Position -> Action (Maybe (Maybe Range , [T. Text ]))
5458blah _ (Position line col)
@@ -99,8 +103,8 @@ mkDiag file diagSource sev loc msg = (file, D.ShowDiag,)
99103-- ---------------------------------------------------------------------
100104
101105-- | Generate code actions.
102- codeAction :: CodeActionProvider IdeState
103- codeAction _lf state _pid (TextDocumentIdentifier uri) _range CodeActionContext {_diagnostics= List _xs} = do
106+ codeAction :: PluginMethodHandler IdeState TextDocumentCodeAction
107+ codeAction state _pid (CodeActionParams _ _ ( TextDocumentIdentifier uri) _range CodeActionContext {_diagnostics= List _xs}) = liftIO $ do
104108 let Just nfp = uriToNormalizedFilePath $ toNormalizedUri uri
105109 Just (ParsedModule {},_) <- runIdeAction " example" (shakeExtras state) $ useWithStaleFast GetParsedModule nfp
106110 let
@@ -109,12 +113,12 @@ codeAction _lf state _pid (TextDocumentIdentifier uri) _range CodeActionContext{
109113 " -- TODO1 added by Example Plugin directly\n " ]
110114 edit = WorkspaceEdit (Just $ Map. singleton uri $ List tedit) Nothing
111115 pure $ Right $ List
112- [ CACodeAction $ CodeAction title (Just CodeActionQuickFix ) (Just $ List [] ) (Just edit) Nothing ]
116+ [ InR $ CodeAction title (Just CodeActionQuickFix ) (Just $ List [] ) Nothing Nothing (Just edit) Nothing ]
113117
114118-- ---------------------------------------------------------------------
115119
116- codeLens :: CodeLensProvider IdeState
117- codeLens _lf ideState plId CodeLensParams {_textDocument= TextDocumentIdentifier uri} = do
120+ codeLens :: PluginMethodHandler IdeState TextDocumentCodeLens
121+ codeLens ideState plId CodeLensParams {_textDocument= TextDocumentIdentifier uri} = liftIO $ do
118122 logInfo (ideLogger ideState) " Example.codeLens entered (ideLogger)" -- AZ
119123 case uriToFilePath' uri of
120124 Just (toNormalizedFilePath -> filePath) -> do
@@ -141,7 +145,7 @@ data AddTodoParams = AddTodoParams
141145 deriving (Show , Eq , Generic , ToJSON , FromJSON )
142146
143147addTodoCmd :: CommandFunction IdeState AddTodoParams
144- addTodoCmd _lf _ide (AddTodoParams uri todoText) = do
148+ addTodoCmd _ide (AddTodoParams uri todoText) = do
145149 let
146150 pos = Position 3 0
147151 textEdits = List
@@ -151,7 +155,8 @@ addTodoCmd _lf _ide (AddTodoParams uri todoText) = do
151155 res = WorkspaceEdit
152156 (Just $ Map. singleton uri textEdits)
153157 Nothing
154- return (Right Null , Just (WorkspaceApplyEdit , ApplyWorkspaceEditParams res))
158+ _ <- sendRequest SWorkspaceApplyEdit (ApplyWorkspaceEditParams Nothing res) (\ _ -> pure () )
159+ return $ Right Null
155160
156161-- ---------------------------------------------------------------------
157162
@@ -170,7 +175,7 @@ request
170175 -> IdeState
171176 -> TextDocumentPositionParams
172177 -> IO (Either ResponseError b )
173- request label getResults notFound found ide (TextDocumentPositionParams (TextDocumentIdentifier uri) pos _ ) = do
178+ request label getResults notFound found ide (TextDocumentPositionParams (TextDocumentIdentifier uri) pos) = do
174179 mbResult <- case uriToFilePath' uri of
175180 Just path -> logAndRunRequest label getResults ide pos path
176181 Nothing -> pure Nothing
@@ -187,9 +192,9 @@ logAndRunRequest label getResults ide pos path = do
187192
188193-- ---------------------------------------------------------------------
189194
190- symbols :: SymbolsProvider IdeState
191- symbols _lf _ide (DocumentSymbolParams _doc _mt )
192- = pure $ Right [r]
195+ symbols :: PluginMethodHandler IdeState TextDocumentDocumentSymbol
196+ symbols _ide _pid (DocumentSymbolParams _ _ _doc )
197+ = pure $ Right $ InL $ List [r]
193198 where
194199 r = DocumentSymbol name detail kind deprecation range selR chList
195200 name = " Example_symbol_name"
@@ -202,9 +207,9 @@ symbols _lf _ide (DocumentSymbolParams _doc _mt)
202207
203208-- ---------------------------------------------------------------------
204209
205- completion :: CompletionProvider IdeState
206- completion _lf _ide (CompletionParams _doc _pos _mctxt _mt )
207- = pure $ Right $ Completions $ List [r]
210+ completion :: PluginMethodHandler IdeState TextDocumentCompletion
211+ completion _ide _pid (CompletionParams _doc _pos _ _ _mctxt )
212+ = pure $ Right $ InL $ List [r]
208213 where
209214 r = CompletionItem label kind tags detail documentation deprecated preselect
210215 sortText filterText insertText insertTextFormat
0 commit comments