Skip to content

Commit

Permalink
Improve documentation for plugins
Browse files Browse the repository at this point in the history
  • Loading branch information
fendor committed Jun 20, 2022
1 parent 290baa0 commit 34251ef
Showing 1 changed file with 100 additions and 30 deletions.
130 changes: 100 additions & 30 deletions hls-plugin-api/src/Ide/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -112,6 +112,7 @@ instance Show (IdeCommand st) where show _ = "<ide command>"

data PluginDescriptor (ideState :: *) =
PluginDescriptor { pluginId :: !PluginId
-- ^ Unique identifier of the plugin.
, pluginRules :: !(Rules ())
, pluginCommands :: ![PluginCommand ideState]
, pluginHandlers :: PluginHandlers ideState
Expand All @@ -126,11 +127,23 @@ data PluginDescriptor (ideState :: *) =
-- The file extension must have a leading '.'.
}

-- | Check whether the given plugin descriptor is responsible for the file with the given path.
-- Compares the file extension of the file at the given path with the file extension
-- the plugin is responsible for.
pluginResponsible :: Uri -> PluginDescriptor c -> Bool
pluginResponsible uri pluginDesc
| Just fp <- mfp
, T.pack (takeExtension fp) `elem` pluginFileType pluginDesc = True
| otherwise = False
where
mfp = uriToFilePath uri

-- | An existential wrapper of 'Properties'
data CustomConfig = forall r. CustomConfig (Properties r)

-- | Describes the configuration a plugin.
-- A plugin may be configurable in such form:
--
-- @
-- {
-- "plugin-id": {
Expand All @@ -143,6 +156,7 @@ data CustomConfig = forall r. CustomConfig (Properties r)
-- }
-- }
-- @
--
-- @globalOn@, @codeActionsOn@, and @codeLensOn@ etc. are called generic configs,
-- which can be inferred from handlers registered by the plugin.
-- @config@ is called custom config, which is defined using 'Properties'.
Expand All @@ -168,24 +182,65 @@ defaultConfigDescriptor = ConfigDescriptor True False (mkCustomConfig emptyPrope
-- Only methods for which we know how to combine responses can be instances of 'PluginMethod'
class HasTracing (MessageParams m) => PluginMethod (k :: MethodType) (m :: Method FromClient k) where

-- | Parse the configuration to check if this plugin is enabled
-- | Parse the configuration to check if this plugin is enabled.
-- Perform sanity checks on the message to see whether plugin is enabled
-- for this message in particular.
-- If a plugin is not enabled, its handlers, commands, etc... will not be
-- run for the given message.
--
-- Semantically, this method described whether a Plugin is enabled configuration wise
-- and is allowed to respond to the message. This might depend on the URI that is
-- associated to the Message Parameters, but doesn't have to. There are requests
-- with no associated URI that, consequentially, can't inspect the URI.
--
-- Common reason why a plugin might not be allowed to respond although it is enabled:
-- * Plugin can not handle requests associated to the specific URI
-- * Since the implementation of [cabal plugins](https://github.com/haskell/haskell-language-server/issues/2940)
-- HLS knows plugins specific for Haskell and specific for [Cabal file descriptions](https://cabal.readthedocs.io/en/3.6/cabal-package.html)
--
-- Strictly speaking, we are conflating two concepts here:
-- * Dynamically enabled (e.g. enabled on a per-message basis)
-- * Statically enabled (e.g. by configuration in the lsp-client)
-- * Strictly speaking, this might also change dynamically
--
-- But there is no use to split it up currently into two different methods for now.
pluginEnabled
:: SMethod m
-- ^ Method type.
-> MessageParams m
-- ^ Whether a plugin is enabled might depend on the message parameters
-- eg 'pluginFileType' specifies what file extension a plugin is allowed to handle
-> PluginDescriptor c
-- ^ Contains meta information such as PluginId and what file types this
-- plugin is able to handle.
-> Config
-- ^ Generic config description, expected to hold 'PluginConfig' configuration
-- for this plugin
-> Bool
-- ^ Is this plugin enabled and allowed to respond to the given request
-- with the given parameters?

default pluginEnabled :: (HasTextDocument (MessageParams m) doc, HasUri doc Uri)
=> SMethod m -> MessageParams m -> PluginDescriptor c -> Config -> Bool
pluginEnabled _ params desc conf = pluginResponsible uri desc && plcGlobalOn (configForPlugin conf (pluginId desc))
where
uri = params ^. J.textDocument . J.uri

-- ---------------------------------------------------------------------
-- Plugin Requests
-- ---------------------------------------------------------------------

class PluginMethod Request m => PluginRequestMethod (m :: Method FromClient Request) where
-- | How to combine responses from different plugins
-- | How to combine responses from different plugins.
--
-- For example, for Hover requests, we might have multiple producers of
-- Hover information, we do not want to decide which one to display to the user
-- but allow here to define how to merge two hover request responses into one
-- glorious hover box.
--
-- However, sometimes only one handler of a request can realistically exist,
-- such as TextDocumentFormatting, it is safe to just unconditionally report
-- back one arbitrary result (arbitrary since it should only be one anyway).
combineResponses
:: SMethod m
-> Config -- ^ IDE Configuration
Expand All @@ -197,7 +252,6 @@ class PluginMethod Request m => PluginRequestMethod (m :: Method FromClient Requ
=> SMethod m -> Config -> ClientCapabilities -> MessageParams m -> NonEmpty (ResponseResult m) -> ResponseResult m
combineResponses _method _config _caps _params = sconcat


instance PluginMethod Request TextDocumentCodeAction where
pluginEnabled _ msgParams pluginDesc config =
pluginResponsible uri pluginDesc && pluginEnabledConfig plcCodeActionsOn (pluginId pluginDesc) config
Expand Down Expand Up @@ -231,17 +285,6 @@ instance PluginRequestMethod TextDocumentCodeAction where
, Just caKind <- ca ^. kind = any (\k -> k `codeActionKindSubsumes` caKind) allowed
| otherwise = False

-- | Check whether the given plugin descriptor is responsible for the file with the given path.
-- Compares the file extension of the file at the given path with the file extension
-- the plugin is responsible for.
pluginResponsible :: Uri -> PluginDescriptor c -> Bool
pluginResponsible uri pluginDesc
| Just fp <- mfp
, T.pack (takeExtension fp) `elem` pluginFileType pluginDesc = True
| otherwise = False
where
mfp = uriToFilePath uri

instance PluginMethod Request TextDocumentDefinition where
pluginEnabled _ msgParams pluginDesc _ =
pluginResponsible uri pluginDesc
Expand All @@ -267,34 +310,34 @@ instance PluginMethod Request TextDocumentReferences where
uri = msgParams ^. J.textDocument . J.uri

instance PluginMethod Request WorkspaceSymbol where
-- Unconditionally enabled, but should it really be?
pluginEnabled _ _ _ _ = True

instance PluginMethod Request TextDocumentCodeLens where
pluginEnabled _ msgParams pluginDesc config =
pluginResponsible uri pluginDesc
pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
&& pluginEnabledConfig plcCodeLensOn (pluginId pluginDesc) config
where
uri = msgParams ^. J.textDocument . J.uri

instance PluginMethod Request TextDocumentRename where
pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
&& pluginEnabledConfig plcRenameOn (pluginId pluginDesc) config
where
uri = msgParams ^. J.textDocument . J.uri
instance PluginMethod Request TextDocumentHover where
pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
&& pluginEnabledConfig plcHoverOn (pluginId pluginDesc) config
where
uri = msgParams ^. J.textDocument . J.uri

instance PluginMethod Request TextDocumentDocumentSymbol where
pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
&& pluginEnabledConfig plcSymbolsOn (pluginId pluginDesc) config
where
uri = msgParams ^. J.textDocument . J.uri

instance PluginMethod Request TextDocumentCompletion where
pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
pluginEnabled _ msgParams pluginDesc config = pluginResponsible uri pluginDesc
&& pluginEnabledConfig plcCompletionOn (pluginId pluginDesc) config
where
uri = msgParams ^. J.textDocument . J.uri
Expand All @@ -321,17 +364,20 @@ instance PluginMethod Request TextDocumentPrepareCallHierarchy where
pid = pluginId pluginDesc

instance PluginMethod Request TextDocumentSelectionRange where
pluginEnabled _ msgParams pluginDesc conf = pluginResponsible uri pluginDesc && pluginEnabledConfig plcSelectionRangeOn pid conf
pluginEnabled _ msgParams pluginDesc conf = pluginResponsible uri pluginDesc
&& pluginEnabledConfig plcSelectionRangeOn pid conf
where
uri = msgParams ^. J.textDocument . J.uri
pid = pluginId pluginDesc

instance PluginMethod Request CallHierarchyIncomingCalls where
-- This method has no URI parameter, thus no call to 'pluginResponsible'
pluginEnabled _ _ pluginDesc conf = pluginEnabledConfig plcCallHierarchyOn pid conf
where
pid = pluginId pluginDesc

instance PluginMethod Request CallHierarchyOutgoingCalls where
-- This method has no URI parameter, thus no call to 'pluginResponsible'
pluginEnabled _ _ pluginDesc conf = pluginEnabledConfig plcCallHierarchyOn pid conf
where
pid = pluginId pluginDesc
Expand Down Expand Up @@ -430,8 +476,13 @@ instance PluginRequestMethod CallHierarchyOutgoingCalls where

instance PluginRequestMethod CustomMethod where
combineResponses _ _ _ _ (x :| _) = x

-- ---------------------------------------------------------------------
-- Plugin Notifications
-- ---------------------------------------------------------------------

-- | Plugin Notification methods. No specific methods at the moment, but
-- might contain more in the future.
class PluginMethod Notification m => PluginNotificationMethod (m :: Method FromClient Notification) where


Expand All @@ -443,27 +494,31 @@ instance PluginMethod Notification TextDocumentDidSave where

instance PluginMethod Notification TextDocumentDidClose where


instance PluginNotificationMethod TextDocumentDidOpen where

instance PluginNotificationMethod TextDocumentDidChange where

instance PluginNotificationMethod TextDocumentDidSave where

instance PluginNotificationMethod TextDocumentDidClose where

instance PluginMethod Notification WorkspaceDidChangeWatchedFiles where
-- This method has no URI parameter, thus no call to 'pluginResponsible'.
pluginEnabled _ _ desc conf = plcGlobalOn $ configForPlugin conf (pluginId desc)

instance PluginMethod Notification WorkspaceDidChangeWorkspaceFolders where
-- This method has no URI parameter, thus no call to 'pluginResponsible'.
pluginEnabled _ _ desc conf = plcGlobalOn $ configForPlugin conf (pluginId desc)

instance PluginMethod Notification WorkspaceDidChangeConfiguration where
-- This method has no URI parameter, thus no call to 'pluginResponsible'.
pluginEnabled _ _ desc conf = plcGlobalOn $ configForPlugin conf (pluginId desc)

instance PluginMethod Notification Initialized where
-- This method has no URI parameter, thus no call to 'pluginResponsible'.
pluginEnabled _ _ desc conf = plcGlobalOn $ configForPlugin conf (pluginId desc)


instance PluginNotificationMethod TextDocumentDidOpen where

instance PluginNotificationMethod TextDocumentDidChange where

instance PluginNotificationMethod TextDocumentDidSave where

instance PluginNotificationMethod TextDocumentDidClose where

instance PluginNotificationMethod WorkspaceDidChangeWatchedFiles where

instance PluginNotificationMethod WorkspaceDidChangeWorkspaceFolders where
Expand Down Expand Up @@ -540,6 +595,15 @@ mkPluginNotificationHandler m f
where
f' pid ide vfs = f ide vfs pid

-- | Set up a plugin descriptor, initialized with default values.
-- This is plugin descriptor is prepared for @haskell@ files, such as
--
-- * @.hs@
-- * @.lhs@
-- * @.hs-boot@
--
-- and handlers will be enabled for files with the appropriate file
-- extensions.
defaultPluginDescriptor :: PluginId -> PluginDescriptor ideState
defaultPluginDescriptor plId =
PluginDescriptor
Expand All @@ -553,6 +617,12 @@ defaultPluginDescriptor plId =
Nothing
[".hs", ".lhs", ".hs-boot"]

-- | Set up a plugin descriptor, initialized with default values.
-- This is plugin descriptor is prepared for @.cabal@ files and as such,
-- will only respond / run when @.cabal@ files are currently in scope.
--
-- Handles files with the following extensions:
-- * @.cabal@
defaultCabalPluginDescriptor :: PluginId -> PluginDescriptor ideState
defaultCabalPluginDescriptor plId =
PluginDescriptor
Expand Down

0 comments on commit 34251ef

Please sign in to comment.