Skip to content

Commit 99dc22e

Browse files
committed
Add example plugin
1 parent 0b2cd7d commit 99dc22e

File tree

2 files changed

+58
-0
lines changed

2 files changed

+58
-0
lines changed

exe/Plugins.hs

Lines changed: 2 additions & 0 deletions
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
]
Lines changed: 56 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,2 +1,58 @@
1+
{-# LANGUAGE DeriveAnyClass #-}
2+
{-# LANGUAGE DeriveGeneric #-}
3+
{-# LANGUAGE DuplicateRecordFields #-}
4+
{-# LANGUAGE FlexibleContexts #-}
5+
{-# LANGUAGE FlexibleInstances #-}
6+
{-# LANGUAGE LambdaCase #-}
7+
{-# LANGUAGE OverloadedStrings #-}
8+
{-# LANGUAGE RecordWildCards #-}
9+
{-# LANGUAGE TupleSections #-}
10+
{-# LANGUAGE TypeFamilies #-}
11+
{-# LANGUAGE ViewPatterns #-}
12+
113
module Ide.Plugin.ExampleCabal where
214

15+
import Control.Monad.IO.Class
16+
import Data.Aeson
17+
import qualified Data.Text as T
18+
import Development.IDE as D
19+
import GHC.Generics
20+
import Ide.PluginUtils
21+
import Ide.Types
22+
import Language.LSP.Types
23+
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+
{ pluginHandlers = mkPluginHandler STextDocumentCodeLens (codeLens recorder)
34+
}
35+
36+
-- ---------------------------------------------------------------------
37+
38+
codeLens :: Recorder (WithPriority Log) -> PluginMethodHandler IdeState TextDocumentCodeLens
39+
codeLens recorder _ideState plId CodeLensParams{_textDocument=TextDocumentIdentifier uri} = liftIO $ do
40+
log Debug $ LogText "ExampleCabal.codeLens entered (ideLogger)"
41+
case uriToFilePath' uri of
42+
Just (toNormalizedFilePath -> _filePath) -> do
43+
let
44+
title = "Add TODO Item via Code Lens"
45+
range = Range (Position 3 0) (Position 4 0)
46+
let cmdParams = AddTodoParams uri "do abc"
47+
cmd = mkLspCommand plId "codelens.todo" title (Just [toJSON cmdParams])
48+
pure $ Right $ List [ CodeLens range (Just cmd) Nothing ]
49+
Nothing -> pure $ Right $ List []
50+
where
51+
log = logWith recorder
52+
-- ---------------------------------------------------------------------
53+
54+
data AddTodoParams = AddTodoParams
55+
{ file :: Uri -- ^ Uri of the file to add the pragma to
56+
, todoText :: T.Text
57+
}
58+
deriving (Show, Eq, Generic, ToJSON, FromJSON)

0 commit comments

Comments
 (0)