Skip to content

Commit a9041fc

Browse files
author
Jana Chadt
committed
Add documentation
Fix ambiguous plugin handler use
1 parent e95a904 commit a9041fc

File tree

3 files changed

+22
-8
lines changed

3 files changed

+22
-8
lines changed

ghcide/src/Development/IDE/LSP/Server.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -18,7 +18,7 @@ module Development.IDE.LSP.Server
1818
import Control.Monad.Reader
1919
import Development.IDE.Core.Shake
2020
import Development.IDE.Core.Tracing
21-
import Ide.Types (HasTracing, traceWithSpan, PluginRequestMethod, PluginNotificationMethod)
21+
import Ide.Types (HasTracing, traceWithSpan)
2222
import Language.LSP.Server (Handlers, LspM)
2323
import qualified Language.LSP.Server as LSP
2424
import Language.LSP.Types

hls-plugin-api/src/Ide/Types.hs

Lines changed: 19 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -119,7 +119,11 @@ data PluginDescriptor (ideState :: *) =
119119
, pluginNotificationHandlers :: PluginNotificationHandlers ideState
120120
, pluginModifyDynflags :: DynFlagsModifications
121121
, pluginCli :: Maybe (ParserInfo (IdeCommand ideState))
122-
, pluginFileType :: [T.Text]
122+
, pluginFileType :: [T.Text]
123+
-- ^ File extension of the files the plugin is responsible for.
124+
-- The plugin is only allowed to handle files with these extensions
125+
-- When writing handlers, etc. for this plugin it can be assumed that all handled files are of this type.
126+
-- The file extension must have a leading '.'.
123127
}
124128

125129
-- | An existential wrapper of 'Properties'
@@ -165,7 +169,14 @@ defaultConfigDescriptor = ConfigDescriptor True False (mkCustomConfig emptyPrope
165169
class HasTracing (MessageParams m) => PluginMethod (k :: MethodType) (m :: Method FromClient k) where
166170

167171
-- | Parse the configuration to check if this plugin is enabled
168-
pluginEnabled :: SMethod m -> MessageParams m -> PluginDescriptor c -> Config -> Bool
172+
pluginEnabled
173+
:: SMethod m
174+
-> MessageParams m
175+
-- ^ Whether a plugin is enabled might depend on the message parameters
176+
-- eg 'pluginFileType' specifies what file extension a plugin is allowed to handle
177+
-> PluginDescriptor c
178+
-> Config
179+
-> Bool
169180

170181
default pluginEnabled :: (HasTextDocument (MessageParams m) doc, HasUri doc Uri)
171182
=> SMethod m -> MessageParams m -> PluginDescriptor c -> Config -> Bool
@@ -220,6 +231,9 @@ instance PluginRequestMethod TextDocumentCodeAction where
220231
, Just caKind <- ca ^. kind = any (\k -> k `codeActionKindSubsumes` caKind) allowed
221232
| otherwise = False
222233

234+
-- | Check whether the given plugin descriptor is responsible for the file with the given path.
235+
-- Compares the file extension of the file at the given path with the file extension
236+
-- the plugin is responsible for.
223237
pluginResponsible :: Uri -> PluginDescriptor c -> Bool
224238
pluginResponsible uri pluginDesc
225239
| Just fp <- mfp
@@ -307,8 +321,9 @@ instance PluginMethod Request TextDocumentPrepareCallHierarchy where
307321
pid = pluginId pluginDesc
308322

309323
instance PluginMethod Request TextDocumentSelectionRange where
310-
pluginEnabled _ _ pluginDesc conf = pluginEnabledConfig plcSelectionRangeOn pid conf
324+
pluginEnabled _ msgParams pluginDesc conf = pluginResponsible uri pluginDesc && pluginEnabledConfig plcSelectionRangeOn pid conf
311325
where
326+
uri = msgParams ^. J.textDocument . J.uri
312327
pid = pluginId pluginDesc
313328

314329
instance PluginMethod Request CallHierarchyIncomingCalls where
@@ -399,7 +414,7 @@ instance PluginRequestMethod TextDocumentCompletion where
399414
consumeCompletionResponse n (InR (CompletionList isCompleteResponse (List xx)))
400415

401416
instance PluginRequestMethod TextDocumentFormatting where
402-
combineResponses _ _ _ _ x = sconcat x
417+
combineResponses _ _ _ _ (x :| _) = x
403418

404419
instance PluginRequestMethod TextDocumentRangeFormatting where
405420
combineResponses _ _ _ _ (x :| _) = x

plugins/default/src/Ide/Plugin/ExampleCabal.hs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,5 @@
11
{-# LANGUAGE DeriveAnyClass #-}
22
{-# LANGUAGE DeriveGeneric #-}
3-
{-# LANGUAGE DuplicateRecordFields #-}
43
{-# LANGUAGE FlexibleContexts #-}
54
{-# LANGUAGE FlexibleInstances #-}
65
{-# LANGUAGE LambdaCase #-}
@@ -15,7 +14,7 @@ module Ide.Plugin.ExampleCabal where
1514
import Control.Monad.IO.Class
1615
import Data.Aeson
1716
import qualified Data.Text as T
18-
import Development.IDE as D
17+
import Development.IDE as D hiding (pluginHandlers)
1918
import GHC.Generics
2019
import Ide.PluginUtils
2120
import Ide.Types
@@ -29,7 +28,7 @@ instance Pretty Log where
2928
LogText log -> pretty log
3029

3130
descriptor :: Recorder (WithPriority Log) -> PluginId -> PluginDescriptor IdeState
32-
descriptor recorder plId = (defaultCabalPluginDescriptor plId)
31+
descriptor recorder plId = (defaultCabalPluginDescriptor plId :: PluginDescriptor IdeState)
3332
{ pluginHandlers = mkPluginHandler STextDocumentCodeLens (codeLens recorder)
3433
}
3534

0 commit comments

Comments
 (0)