Skip to content

Commit

Permalink
Add example plugin
Browse files Browse the repository at this point in the history
  • Loading branch information
fendor committed Jun 9, 2022
1 parent 9c494ca commit 386bf8a
Show file tree
Hide file tree
Showing 2 changed files with 53 additions and 0 deletions.
2 changes: 2 additions & 0 deletions exe/Plugins.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,6 +13,7 @@ import Development.IDE (IdeState)
import qualified Development.IDE.Plugin.HLS.GhcIde as GhcIde
import qualified Ide.Plugin.Example as Example
import qualified Ide.Plugin.Example2 as Example2
import qualified Ide.Plugin.ExampleCabal as ExampleCabal

-- haskell-language-server optional plugins
#if qualifyImportedNames
Expand Down Expand Up @@ -204,4 +205,5 @@ idePlugins recorder includeExamples = pluginDescToIdePlugins allPlugins
examplePlugins =
[Example.descriptor pluginRecorder "eg"
,Example2.descriptor pluginRecorder "eg2"
,ExampleCabal.descriptor pluginRecorder "ec"
]
51 changes: 51 additions & 0 deletions plugins/default/src/Ide/Plugin/ExampleCabal.hs
Original file line number Diff line number Diff line change
@@ -1,2 +1,53 @@
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE OverloadedStrings #-}
module Ide.Plugin.ExampleCabal where

import Data.Aeson
import qualified Data.HashMap.Strict as Map
import qualified Data.Text as T
import Development.IDE as D
import qualified Development.IDE.Core.Shake as Shake
import GHC.Generics
import Ide.Types
import Language.LSP.Server
import Language.LSP.Types
import Text.Regex.TDFA.Text ()


newtype Log = LogShake Shake.Log deriving Show

instance Pretty Log where
pretty = \case
LogShake log -> pretty log

descriptor :: Recorder (WithPriority Log) -> PluginId -> PluginDescriptor IdeState
descriptor _recorder plId = (defaultCabalPluginDescriptor plId)
{ pluginCommands = [PluginCommand "codelens.todo" "example adding" addTodoCmd]
}

-- ---------------------------------------------------------------------
-- | Parameters for the addTodo PluginCommand.
data AddTodoParams = AddTodoParams
{ file :: Uri -- ^ Uri of the file to add the pragma to
, todoText :: T.Text
}
deriving (Show, Eq, Generic, ToJSON, FromJSON)

addTodoCmd :: CommandFunction IdeState AddTodoParams
addTodoCmd _ide (AddTodoParams uri todoText) = do
let
pos = Position 3 0
textEdits = List
[TextEdit (Range pos pos)
("-- TODO:" <> todoText <> "\n")
]
res = WorkspaceEdit
(Just $ Map.singleton uri textEdits)
Nothing
Nothing
_ <- sendRequest SWorkspaceApplyEdit (ApplyWorkspaceEditParams Nothing res) (\_ -> pure ())
return $ Right Null

-- ---------------------------------------------------------------------

0 comments on commit 386bf8a

Please sign in to comment.