Skip to content

Commit c8eb96b

Browse files
committed
Add example plugin
1 parent 53b903e commit c8eb96b

File tree

2 files changed

+75
-0
lines changed

2 files changed

+75
-0
lines changed

exe/Plugins.hs

+2
Original file line numberDiff line numberDiff line change
@@ -13,6 +13,7 @@ import Development.IDE (IdeState)
1313
import qualified Development.IDE.Plugin.HLS.GhcIde as GhcIde
1414
import qualified Ide.Plugin.Example as Example
1515
import qualified Ide.Plugin.Example2 as Example2
16+
import qualified Ide.Plugin.ExampleCabal as ExampleCabal
1617

1718
-- haskell-language-server optional plugins
1819
#if qualifyImportedNames
@@ -204,4 +205,5 @@ idePlugins recorder includeExamples = pluginDescToIdePlugins allPlugins
204205
examplePlugins =
205206
[Example.descriptor pluginRecorder "eg"
206207
,Example2.descriptor pluginRecorder "eg2"
208+
,ExampleCabal.descriptor pluginRecorder "ec"
207209
]
Original file line numberDiff line numberDiff line change
@@ -1,2 +1,75 @@
1+
{-# LANGUAGE DeriveAnyClass #-}
2+
{-# LANGUAGE DeriveGeneric #-}
3+
{-# LANGUAGE FlexibleContexts #-}
4+
{-# LANGUAGE FlexibleInstances #-}
5+
{-# LANGUAGE LambdaCase #-}
6+
{-# LANGUAGE OverloadedStrings #-}
7+
{-# LANGUAGE RecordWildCards #-}
8+
{-# LANGUAGE TupleSections #-}
9+
{-# LANGUAGE TypeFamilies #-}
10+
{-# LANGUAGE ViewPatterns #-}
11+
112
module Ide.Plugin.ExampleCabal where
213

14+
import Control.Monad.IO.Class
15+
import Data.Aeson
16+
import qualified Data.HashMap.Strict as Map
17+
import qualified Data.Text as T
18+
import Development.IDE as D hiding (pluginHandlers)
19+
import GHC.Generics
20+
import Ide.PluginUtils
21+
import Ide.Types
22+
import Language.LSP.Server
23+
import Language.LSP.Types
24+
25+
newtype Log = LogText T.Text deriving Show
26+
27+
instance Pretty Log where
28+
pretty = \case
29+
LogText log -> pretty log
30+
31+
descriptor :: Recorder (WithPriority Log) -> PluginId -> PluginDescriptor IdeState
32+
descriptor recorder plId = (defaultCabalPluginDescriptor plId)
33+
{ pluginCommands = [PluginCommand "codelens.todo" "example adding" addTodoCmd]
34+
, pluginHandlers = mkPluginHandler STextDocumentCodeLens (codeLens recorder)
35+
}
36+
37+
-- ---------------------------------------------------------------------
38+
39+
codeLens :: Recorder (WithPriority Log) -> PluginMethodHandler IdeState TextDocumentCodeLens
40+
codeLens recorder _ideState plId CodeLensParams{_textDocument=TextDocumentIdentifier uri} = liftIO $ do
41+
log Debug $ LogText "ExampleCabal.codeLens entered (ideLogger)"
42+
case uriToFilePath' uri of
43+
Just (toNormalizedFilePath -> _filePath) -> do
44+
let
45+
title = "Add TODO Item via Code Lens"
46+
range = Range (Position 3 0) (Position 4 0)
47+
let cmdParams = AddTodoParams uri "do abc"
48+
cmd = mkLspCommand plId "codelens.todo" title (Just [toJSON cmdParams])
49+
pure $ Right $ List [ CodeLens range (Just cmd) Nothing ]
50+
Nothing -> pure $ Right $ List []
51+
where
52+
log = logWith recorder
53+
54+
-- ---------------------------------------------------------------------
55+
-- | Parameters for the addTodo PluginCommand.
56+
data AddTodoParams = AddTodoParams
57+
{ file :: Uri -- ^ Uri of the file to add the pragma to
58+
, todoText :: T.Text
59+
}
60+
deriving (Show, Eq, Generic, ToJSON, FromJSON)
61+
62+
addTodoCmd :: CommandFunction IdeState AddTodoParams
63+
addTodoCmd _ide (AddTodoParams uri todoText) = do
64+
let
65+
pos = Position 5 0
66+
textEdits = List
67+
[TextEdit (Range pos pos)
68+
("-- TODO2:" <> todoText <> "\n")
69+
]
70+
res = WorkspaceEdit
71+
(Just $ Map.singleton uri textEdits)
72+
Nothing
73+
Nothing
74+
_ <- sendRequest SWorkspaceApplyEdit (ApplyWorkspaceEditParams Nothing res) (\_ -> pure ())
75+
return $ Right Null

0 commit comments

Comments
 (0)