Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Synopsis
- data PluginDescriptor (ideState :: Type) = PluginDescriptor {
- pluginId :: !PluginId
- pluginDescription :: !Text
- pluginPriority :: Natural
- pluginRules :: !(Rules ())
- pluginCommands :: ![PluginCommand ideState]
- pluginHandlers :: PluginHandlers ideState
- pluginConfigDescriptor :: ConfigDescriptor
- pluginNotificationHandlers :: PluginNotificationHandlers ideState
- pluginModifyDynflags :: DynFlagsModifications
- pluginCli :: Maybe (ParserInfo (IdeCommand ideState))
- pluginFileType :: [Text]
- defaultPluginDescriptor :: PluginId -> Text -> PluginDescriptor ideState
- defaultCabalPluginDescriptor :: PluginId -> Text -> PluginDescriptor ideState
- defaultPluginPriority :: Natural
- describePlugin :: PluginDescriptor c -> Doc ann
- newtype IdeCommand state = IdeCommand (state -> IO ())
- data IdeMethod (m :: Method ClientToServer Request) = PluginRequestMethod m => IdeMethod (SMethod m)
- data IdeNotification (m :: Method ClientToServer Notification) = PluginNotificationMethod m => IdeNotification (SMethod m)
- data IdePlugins ideState where
- pattern IdePlugins :: [PluginDescriptor ideState] -> IdePlugins ideState
- data DynFlagsModifications = DynFlagsModifications {}
- data Config = Config {}
- data PluginConfig = PluginConfig {
- plcGlobalOn :: !Bool
- plcCallHierarchyOn :: !Bool
- plcCodeActionsOn :: !Bool
- plcCodeLensOn :: !Bool
- plcDiagnosticsOn :: !Bool
- plcHoverOn :: !Bool
- plcSymbolsOn :: !Bool
- plcCompletionOn :: !Bool
- plcRenameOn :: !Bool
- plcSelectionRangeOn :: !Bool
- plcFoldingRangeOn :: !Bool
- plcSemanticTokensOn :: !Bool
- plcConfig :: !Object
- data CheckParents
- data SessionLoadingPreferenceConfig
- data ConfigDescriptor = ConfigDescriptor {}
- defaultConfigDescriptor :: ConfigDescriptor
- configForPlugin :: Config -> PluginDescriptor c -> PluginConfig
- data CustomConfig = forall r. CustomConfig (Properties r)
- mkCustomConfig :: Properties r -> CustomConfig
- data FallbackCodeActionParams = FallbackCodeActionParams {
- fallbackWorkspaceEdit :: Maybe WorkspaceEdit
- fallbackCommand :: Maybe Command
- data FormattingType
- = FormatText
- | FormatRange Range
- type FormattingMethod m = (HasOptions (MessageParams m) FormattingOptions, HasTextDocument (MessageParams m) TextDocumentIdentifier, MessageResult m ~ ([TextEdit] |? Null))
- type FormattingHandler a = a -> Maybe ProgressToken -> FormattingType -> Text -> NormalizedFilePath -> FormattingOptions -> ExceptT PluginError (HandlerM Config) ([TextEdit] |? Null)
- mkFormattingHandlers :: forall a. FormattingHandler a -> PluginHandlers a
- class HasTracing a where
- traceWithSpan :: SpanInFlight -> a -> IO ()
- data PluginCommand ideState = forall a.FromJSON a => PluginCommand {
- commandId :: CommandId
- commandDesc :: Text
- commandFunc :: CommandFunction ideState a
- newtype CommandId = CommandId Text
- type CommandFunction ideState a = ideState -> Maybe ProgressToken -> a -> ExceptT PluginError (HandlerM Config) (Value |? Null)
- mkLspCommand :: PluginId -> CommandId -> Text -> Maybe [Value] -> Command
- mkLspCmdId :: Text -> PluginId -> CommandId -> Text
- newtype PluginId = PluginId Text
- newtype PluginHandler a (m :: Method ClientToServer Request) = PluginHandler (PluginId -> a -> MessageParams m -> HandlerM Config (NonEmpty (Either PluginError (MessageResult m))))
- mkPluginHandler :: forall ideState m. PluginRequestMethod m => SClientMethod m -> PluginMethodHandler ideState m -> PluginHandlers ideState
- data HandlerM config a
- runHandlerM :: HandlerM config a -> LspM config a
- pluginGetClientCapabilities :: HandlerM config ClientCapabilities
- pluginGetVirtualFile :: NormalizedUri -> HandlerM config (Maybe VirtualFile)
- pluginGetVersionedTextDoc :: TextDocumentIdentifier -> HandlerM config VersionedTextDocumentIdentifier
- pluginSendNotification :: forall (m :: Method ServerToClient Notification) config. SServerMethod m -> MessageParams m -> HandlerM config ()
- pluginSendRequest :: forall (m :: Method ServerToClient Request) config. SServerMethod m -> MessageParams m -> (Either (TResponseError m) (MessageResult m) -> HandlerM config ()) -> HandlerM config (LspId m)
- pluginWithIndefiniteProgress :: Text -> Maybe ProgressToken -> ProgressCancellable -> ((Text -> HandlerM config ()) -> HandlerM config a) -> HandlerM config a
- newtype PluginHandlers a = PluginHandlers (DMap IdeMethod (PluginHandler a))
- class HasTracing (MessageParams m) => PluginMethod (k :: MessageKind) (m :: Method ClientToServer k) where
- handlesRequest :: SMethod m -> MessageParams m -> PluginDescriptor c -> Config -> HandleRequestResult
- type PluginMethodHandler a m = a -> PluginId -> MessageParams m -> ExceptT PluginError (HandlerM Config) (MessageResult m)
- newtype PluginNotificationHandler a (m :: Method ClientToServer Notification) = PluginNotificationHandler (PluginId -> a -> VFS -> MessageParams m -> LspM Config ())
- mkPluginNotificationHandler :: PluginNotificationMethod m => SClientMethod (m :: Method ClientToServer Notification) -> PluginNotificationMethodHandler ideState m -> PluginNotificationHandlers ideState
- newtype PluginNotificationHandlers a = PluginNotificationHandlers (DMap IdeNotification (PluginNotificationHandler a))
- class PluginMethod Request m => PluginRequestMethod (m :: Method ClientToServer Request) where
- combineResponses :: SMethod m -> Config -> ClientCapabilities -> MessageParams m -> NonEmpty (MessageResult m) -> MessageResult m
- getProcessID :: IO Int
- getPid :: IO Text
- installSigUsr1Handler :: IO () -> IO ()
- $sel:lookupCommandProvider:IdePlugins_ :: IdePlugins ideState -> CommandId -> Maybe PluginId
- type ResolveFunction ideState a (m :: Method ClientToServer Request) = ideState -> PluginId -> MessageParams m -> Uri -> a -> ExceptT PluginError (HandlerM Config) (MessageResult m)
- mkResolveHandler :: forall ideState a m. (FromJSON a, PluginRequestMethod m, HasData_ (MessageParams m) (Maybe Value)) => SClientMethod m -> ResolveFunction ideState a m -> PluginHandlers ideState
Documentation
data PluginDescriptor (ideState :: Type) Source #
PluginDescriptor | |
|
defaultPluginDescriptor :: PluginId -> Text -> PluginDescriptor ideState Source #
Set up a plugin descriptor, initialized with default values.
This 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.
defaultCabalPluginDescriptor :: PluginId -> Text -> PluginDescriptor ideState Source #
Set up a plugin descriptor, initialized with default values.
This 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
describePlugin :: PluginDescriptor c -> Doc ann Source #
newtype IdeCommand state Source #
IdeCommand (state -> IO ()) |
Instances
Show (IdeCommand st) Source # | |
Defined in Ide.Types showsPrec :: Int -> IdeCommand st -> ShowS # show :: IdeCommand st -> String # showList :: [IdeCommand st] -> ShowS # |
data IdeMethod (m :: Method ClientToServer Request) Source #
Methods which have a PluginMethod instance
PluginRequestMethod m => IdeMethod (SMethod m) |
data IdeNotification (m :: Method ClientToServer Notification) Source #
Methods which have a PluginMethod instance
PluginNotificationMethod m => IdeNotification (SMethod m) |
Instances
GCompare IdeNotification Source # | |
Defined in Ide.Types gcompare :: forall (a :: k) (b :: k). IdeNotification a -> IdeNotification b -> GOrdering a b # | |
GEq IdeNotification Source # | |
Defined in Ide.Types geq :: forall (a :: k) (b :: k). IdeNotification a -> IdeNotification b -> Maybe (a :~: b) # |
data IdePlugins ideState where Source #
pattern IdePlugins :: [PluginDescriptor ideState] -> IdePlugins ideState | Smart constructor that deduplicates plugins |
Instances
Monoid (IdePlugins a) Source # | |
Defined in Ide.Types mempty :: IdePlugins a # mappend :: IdePlugins a -> IdePlugins a -> IdePlugins a # mconcat :: [IdePlugins a] -> IdePlugins a # | |
Semigroup (IdePlugins a) Source # | |
Defined in Ide.Types (<>) :: IdePlugins a -> IdePlugins a -> IdePlugins a # sconcat :: NonEmpty (IdePlugins a) -> IdePlugins a # stimes :: Integral b => b -> IdePlugins a -> IdePlugins a # |
data DynFlagsModifications Source #
Hooks for modifying the DynFlags
at different times of the compilation
process. Plugins can install a DynFlagsModifications
via
$sel:pluginModifyDynflags:PluginDescriptor
in their PluginDescriptor
.
DynFlagsModifications | |
|
Instances
Monoid DynFlagsModifications Source # | |
Defined in Ide.Types | |
Semigroup DynFlagsModifications Source # | |
Defined in Ide.Types |
We (initially anyway) mirror the hie configuration, so that existing clients can simply switch executable and not have any nasty surprises. There will initially be surprises relating to config options being ignored though.
data PluginConfig Source #
A PluginConfig is a generic configuration for a given HLS plugin. It provides a "big switch" to turn it on or off as a whole, as well as small switches per feature, and a slot for custom config. This provides a regular naming scheme for all plugin config.
PluginConfig | |
|
Instances
ToJSON PluginConfig Source # | |
Defined in Ide.Types toJSON :: PluginConfig -> Value # toEncoding :: PluginConfig -> Encoding # toJSONList :: [PluginConfig] -> Value # toEncodingList :: [PluginConfig] -> Encoding # omitField :: PluginConfig -> Bool # | |
Show PluginConfig Source # | |
Defined in Ide.Types showsPrec :: Int -> PluginConfig -> ShowS # show :: PluginConfig -> String # showList :: [PluginConfig] -> ShowS # | |
Default PluginConfig Source # | |
Defined in Ide.Types def :: PluginConfig # | |
Eq PluginConfig Source # | |
Defined in Ide.Types (==) :: PluginConfig -> PluginConfig -> Bool # (/=) :: PluginConfig -> PluginConfig -> Bool # |
data CheckParents Source #
Instances
data SessionLoadingPreferenceConfig Source #
PreferSingleComponentLoading | Always load only a singleComponent when a new component is discovered. |
PreferMultiComponentLoading | Always prefer loading multiple components in the cradle at once. This might not be always possible, if the tool doesn't support multiple components loading. The cradle can decide how to handle these situations, and whether to honour the preference at all. |
Instances
data ConfigDescriptor Source #
Describes the configuration of a plugin. A plugin may be configurable as can be seen below:
{ "plugin-id": { "globalOn": true, "codeActionsOn": true, "codeLensOn": true, "config": { "property1": "foo" } } }
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
.
ConfigDescriptor | |
|
configForPlugin :: Config -> PluginDescriptor c -> PluginConfig Source #
Lookup the current config for a plugin
mkCustomConfig :: Properties r -> CustomConfig Source #
data FallbackCodeActionParams Source #
FallbackCodeActionParams | |
|
Instances
FromJSON FallbackCodeActionParams Source # | |
Defined in Ide.Types | |
ToJSON FallbackCodeActionParams Source # | |
Defined in Ide.Types | |
Generic FallbackCodeActionParams Source # | |
type Rep FallbackCodeActionParams Source # | |
Defined in Ide.Types type Rep FallbackCodeActionParams = D1 ('MetaData "FallbackCodeActionParams" "Ide.Types" "hls-plugin-api-2.9.0.0-7CgpzEGM3js8Q4N91fQzKl" 'False) (C1 ('MetaCons "FallbackCodeActionParams" 'PrefixI 'True) (S1 ('MetaSel ('Just "fallbackWorkspaceEdit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe WorkspaceEdit)) :*: S1 ('MetaSel ('Just "fallbackCommand") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Command)))) |
data FormattingType Source #
Format the given Text as a whole or only a Range
of it.
Range must be relative to the text to format.
To format the whole document, read the Text from the file and use FormatText
as the FormattingType.
FormatText | |
FormatRange Range |
type FormattingMethod m = (HasOptions (MessageParams m) FormattingOptions, HasTextDocument (MessageParams m) TextDocumentIdentifier, MessageResult m ~ ([TextEdit] |? Null)) Source #
type FormattingHandler a = a -> Maybe ProgressToken -> FormattingType -> Text -> NormalizedFilePath -> FormattingOptions -> ExceptT PluginError (HandlerM Config) ([TextEdit] |? Null) Source #
mkFormattingHandlers :: forall a. FormattingHandler a -> PluginHandlers a Source #
class HasTracing a where Source #
Nothing
traceWithSpan :: SpanInFlight -> a -> IO () Source #
Instances
HasTracing Value Source # | |
Defined in Ide.Types traceWithSpan :: SpanInFlight -> Value -> IO () Source # | |
HasTracing CallHierarchyIncomingCallsParams Source # | |
Defined in Ide.Types traceWithSpan :: SpanInFlight -> CallHierarchyIncomingCallsParams -> IO () Source # | |
HasTracing CallHierarchyOutgoingCallsParams Source # | |
Defined in Ide.Types traceWithSpan :: SpanInFlight -> CallHierarchyOutgoingCallsParams -> IO () Source # | |
HasTracing CodeAction Source # | |
Defined in Ide.Types traceWithSpan :: SpanInFlight -> CodeAction -> IO () Source # | |
HasTracing CodeLens Source # | |
Defined in Ide.Types traceWithSpan :: SpanInFlight -> CodeLens -> IO () Source # | |
HasTracing CompletionItem Source # | |
Defined in Ide.Types traceWithSpan :: SpanInFlight -> CompletionItem -> IO () Source # | |
HasTracing DidChangeConfigurationParams Source # | |
Defined in Ide.Types traceWithSpan :: SpanInFlight -> DidChangeConfigurationParams -> IO () Source # | |
HasTracing DidChangeWatchedFilesParams Source # | |
Defined in Ide.Types traceWithSpan :: SpanInFlight -> DidChangeWatchedFilesParams -> IO () Source # | |
HasTracing DidChangeWorkspaceFoldersParams Source # | |
Defined in Ide.Types traceWithSpan :: SpanInFlight -> DidChangeWorkspaceFoldersParams -> IO () Source # | |
HasTracing DocumentLink Source # | |
Defined in Ide.Types traceWithSpan :: SpanInFlight -> DocumentLink -> IO () Source # | |
HasTracing ExecuteCommandParams Source # | |
Defined in Ide.Types traceWithSpan :: SpanInFlight -> ExecuteCommandParams -> IO () Source # | |
HasTracing InitializeParams Source # | |
Defined in Ide.Types traceWithSpan :: SpanInFlight -> InitializeParams -> IO () Source # | |
HasTracing InitializedParams Source # | |
Defined in Ide.Types traceWithSpan :: SpanInFlight -> InitializedParams -> IO () Source # | |
HasTracing InlayHint Source # | |
Defined in Ide.Types traceWithSpan :: SpanInFlight -> InlayHint -> IO () Source # | |
HasTracing WorkspaceSymbol Source # | |
Defined in Ide.Types traceWithSpan :: SpanInFlight -> WorkspaceSymbol -> IO () Source # | |
HasTracing WorkspaceSymbolParams Source # | |
Defined in Ide.Types traceWithSpan :: SpanInFlight -> WorkspaceSymbolParams -> IO () Source # | |
(HasTextDocument a doc, HasUri doc Uri) => HasTracing a Source # | |
Defined in Ide.Types traceWithSpan :: SpanInFlight -> a -> IO () Source # |
data PluginCommand ideState Source #
forall a.FromJSON a => PluginCommand | |
|
type CommandFunction ideState a = ideState -> Maybe ProgressToken -> a -> ExceptT PluginError (HandlerM Config) (Value |? Null) Source #
newtype PluginHandler a (m :: Method ClientToServer Request) Source #
Combine handlers for the
PluginHandler (PluginId -> a -> MessageParams m -> HandlerM Config (NonEmpty (Either PluginError (MessageResult m)))) |
mkPluginHandler :: forall ideState m. PluginRequestMethod m => SClientMethod m -> PluginMethodHandler ideState m -> PluginHandlers ideState Source #
Make a handler for plugins. For how resolve works with this see Note [Resolve in PluginHandlers]
data HandlerM config a Source #
Restricted version of LspM
specific to plugins.
We plan to use this monad for running plugins instead of LspM
, since there
are parts of the LSP server state which plugins should not access directly,
but instead only via the build system. Note that this restriction of the LSP
server state has not yet been implemented. See pluginGetVirtualFile
.
Instances
MonadIO (HandlerM config) Source # | |
Applicative (HandlerM config) Source # | |
Defined in Ide.Types pure :: a -> HandlerM config a # (<*>) :: HandlerM config (a -> b) -> HandlerM config a -> HandlerM config b # liftA2 :: (a -> b -> c) -> HandlerM config a -> HandlerM config b -> HandlerM config c # (*>) :: HandlerM config a -> HandlerM config b -> HandlerM config b # (<*) :: HandlerM config a -> HandlerM config b -> HandlerM config a # | |
Functor (HandlerM config) Source # | |
Monad (HandlerM config) Source # | |
MonadUnliftIO (HandlerM config) Source # | |
runHandlerM :: HandlerM config a -> LspM config a Source #
pluginGetClientCapabilities :: HandlerM config ClientCapabilities Source #
Wrapper of getClientCapabilities
for HandlerM
pluginGetVirtualFile :: NormalizedUri -> HandlerM config (Maybe VirtualFile) Source #
Wrapper of getVirtualFile
for HandlerM
TODO: To be replaced by a lookup of the Shake build graph
pluginGetVersionedTextDoc :: TextDocumentIdentifier -> HandlerM config VersionedTextDocumentIdentifier Source #
Version of getVersionedTextDoc
for HandlerM
TODO: Should use pluginGetVirtualFile
instead of wrapping getVersionedTextDoc
.
At the time of writing, getVersionedTextDoc
of the "lsp" package is implemented with getVirtualFile
.
pluginSendNotification :: forall (m :: Method ServerToClient Notification) config. SServerMethod m -> MessageParams m -> HandlerM config () Source #
Wrapper of 'sendNotification for HandlerM
TODO: Return notification in result instead of calling sendNotification
directly
pluginSendRequest :: forall (m :: Method ServerToClient Request) config. SServerMethod m -> MessageParams m -> (Either (TResponseError m) (MessageResult m) -> HandlerM config ()) -> HandlerM config (LspId m) Source #
Wrapper of sendRequest
for HandlerM
TODO: Return request in result instead of calling sendRequest
directly
pluginWithIndefiniteProgress :: Text -> Maybe ProgressToken -> ProgressCancellable -> ((Text -> HandlerM config ()) -> HandlerM config a) -> HandlerM config a Source #
Wrapper of withIndefiniteProgress
for HandlerM
newtype PluginHandlers a Source #
Instances
Monoid (PluginHandlers a) Source # | |
Defined in Ide.Types mempty :: PluginHandlers a # mappend :: PluginHandlers a -> PluginHandlers a -> PluginHandlers a # mconcat :: [PluginHandlers a] -> PluginHandlers a # | |
Semigroup (PluginHandlers a) Source # | |
Defined in Ide.Types (<>) :: PluginHandlers a -> PluginHandlers a -> PluginHandlers a # sconcat :: NonEmpty (PluginHandlers a) -> PluginHandlers a # stimes :: Integral b => b -> PluginHandlers a -> PluginHandlers a # |
class HasTracing (MessageParams m) => PluginMethod (k :: MessageKind) (m :: Method ClientToServer k) where Source #
Methods that can be handled by plugins.
ExtraParams
captures any extra data the IDE passes to the handlers for this method
Only methods for which we know how to combine responses can be instances of PluginMethod
Nothing
:: SMethod m | Method type. |
-> MessageParams m | Whether a plugin is enabled might depend on the message parameters
e.g. |
-> PluginDescriptor c | Contains meta information such as PluginId and which file types this plugin is able to handle. |
-> Config | Generic config description, expected to contain |
-> HandleRequestResult | Is this plugin enabled and allowed to respond to the given request with the given parameters? |
Parse the configuration to check if this plugin is globally enabled, and if the feature which handles this method is enabled. Perform sanity checks on the message to see whether the plugin handles this message in particular. This class is only used to determine whether a plugin can handle a specific request. Commands and rules do not use this logic to determine whether or not they are run.
A common reason why a plugin won't handle a request even though it is enabled: * The plugin cannot handle requests associated with the specific URI * Since the implementation of cabal plugins HLS knows plugins specific to Haskell and specific to Cabal file descriptions * The resolve request is not routed to that specific plugin. Each resolve request needs to be routed to only one plugin.
Strictly speaking, we are conflating two concepts here: * Dynamically enabled (e.g. 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 into two different methods for now.
default handlesRequest :: (HasTextDocument (MessageParams m) doc, HasUri doc Uri) => SMethod m -> MessageParams m -> PluginDescriptor c -> Config -> HandleRequestResult Source #
Instances
PluginMethod 'Notification 'Method_Initialized Source # | |
Defined in Ide.Types handlesRequest :: SMethod 'Method_Initialized -> MessageParams 'Method_Initialized -> PluginDescriptor c -> Config -> HandleRequestResult Source # | |
PluginMethod 'Notification 'Method_TextDocumentDidChange Source # | |
Defined in Ide.Types handlesRequest :: SMethod 'Method_TextDocumentDidChange -> MessageParams 'Method_TextDocumentDidChange -> PluginDescriptor c -> Config -> HandleRequestResult Source # | |
PluginMethod 'Notification 'Method_TextDocumentDidClose Source # | |
Defined in Ide.Types handlesRequest :: SMethod 'Method_TextDocumentDidClose -> MessageParams 'Method_TextDocumentDidClose -> PluginDescriptor c -> Config -> HandleRequestResult Source # | |
PluginMethod 'Notification 'Method_TextDocumentDidOpen Source # | |
Defined in Ide.Types handlesRequest :: SMethod 'Method_TextDocumentDidOpen -> MessageParams 'Method_TextDocumentDidOpen -> PluginDescriptor c -> Config -> HandleRequestResult Source # | |
PluginMethod 'Notification 'Method_TextDocumentDidSave Source # | |
Defined in Ide.Types handlesRequest :: SMethod 'Method_TextDocumentDidSave -> MessageParams 'Method_TextDocumentDidSave -> PluginDescriptor c -> Config -> HandleRequestResult Source # | |
PluginMethod 'Notification 'Method_WorkspaceDidChangeConfiguration Source # | |
Defined in Ide.Types handlesRequest :: SMethod 'Method_WorkspaceDidChangeConfiguration -> MessageParams 'Method_WorkspaceDidChangeConfiguration -> PluginDescriptor c -> Config -> HandleRequestResult Source # | |
PluginMethod 'Notification 'Method_WorkspaceDidChangeWatchedFiles Source # | |
Defined in Ide.Types handlesRequest :: SMethod 'Method_WorkspaceDidChangeWatchedFiles -> MessageParams 'Method_WorkspaceDidChangeWatchedFiles -> PluginDescriptor c -> Config -> HandleRequestResult Source # | |
PluginMethod 'Notification 'Method_WorkspaceDidChangeWorkspaceFolders Source # | |
Defined in Ide.Types handlesRequest :: SMethod 'Method_WorkspaceDidChangeWorkspaceFolders -> MessageParams 'Method_WorkspaceDidChangeWorkspaceFolders -> PluginDescriptor c -> Config -> HandleRequestResult Source # | |
PluginMethod 'Request 'Method_CallHierarchyIncomingCalls Source # | |
Defined in Ide.Types handlesRequest :: SMethod 'Method_CallHierarchyIncomingCalls -> MessageParams 'Method_CallHierarchyIncomingCalls -> PluginDescriptor c -> Config -> HandleRequestResult Source # | |
PluginMethod 'Request 'Method_CallHierarchyOutgoingCalls Source # | |
Defined in Ide.Types handlesRequest :: SMethod 'Method_CallHierarchyOutgoingCalls -> MessageParams 'Method_CallHierarchyOutgoingCalls -> PluginDescriptor c -> Config -> HandleRequestResult Source # | |
PluginMethod 'Request 'Method_CodeActionResolve Source # | |
Defined in Ide.Types handlesRequest :: SMethod 'Method_CodeActionResolve -> MessageParams 'Method_CodeActionResolve -> PluginDescriptor c -> Config -> HandleRequestResult Source # | |
PluginMethod 'Request 'Method_CodeLensResolve Source # | |
Defined in Ide.Types handlesRequest :: SMethod 'Method_CodeLensResolve -> MessageParams 'Method_CodeLensResolve -> PluginDescriptor c -> Config -> HandleRequestResult Source # | |
PluginMethod 'Request 'Method_CompletionItemResolve Source # | |
Defined in Ide.Types handlesRequest :: SMethod 'Method_CompletionItemResolve -> MessageParams 'Method_CompletionItemResolve -> PluginDescriptor c -> Config -> HandleRequestResult Source # | |
PluginMethod 'Request 'Method_TextDocumentCodeAction Source # | |
Defined in Ide.Types handlesRequest :: SMethod 'Method_TextDocumentCodeAction -> MessageParams 'Method_TextDocumentCodeAction -> PluginDescriptor c -> Config -> HandleRequestResult Source # | |
PluginMethod 'Request 'Method_TextDocumentCodeLens Source # | |
Defined in Ide.Types handlesRequest :: SMethod 'Method_TextDocumentCodeLens -> MessageParams 'Method_TextDocumentCodeLens -> PluginDescriptor c -> Config -> HandleRequestResult Source # | |
PluginMethod 'Request 'Method_TextDocumentCompletion Source # | |
Defined in Ide.Types handlesRequest :: SMethod 'Method_TextDocumentCompletion -> MessageParams 'Method_TextDocumentCompletion -> PluginDescriptor c -> Config -> HandleRequestResult Source # | |
PluginMethod 'Request 'Method_TextDocumentDefinition Source # | |
Defined in Ide.Types handlesRequest :: SMethod 'Method_TextDocumentDefinition -> MessageParams 'Method_TextDocumentDefinition -> PluginDescriptor c -> Config -> HandleRequestResult Source # | |
PluginMethod 'Request 'Method_TextDocumentDocumentHighlight Source # | |
Defined in Ide.Types handlesRequest :: SMethod 'Method_TextDocumentDocumentHighlight -> MessageParams 'Method_TextDocumentDocumentHighlight -> PluginDescriptor c -> Config -> HandleRequestResult Source # | |
PluginMethod 'Request 'Method_TextDocumentDocumentSymbol Source # | |
Defined in Ide.Types handlesRequest :: SMethod 'Method_TextDocumentDocumentSymbol -> MessageParams 'Method_TextDocumentDocumentSymbol -> PluginDescriptor c -> Config -> HandleRequestResult Source # | |
PluginMethod 'Request 'Method_TextDocumentFoldingRange Source # | |
Defined in Ide.Types handlesRequest :: SMethod 'Method_TextDocumentFoldingRange -> MessageParams 'Method_TextDocumentFoldingRange -> PluginDescriptor c -> Config -> HandleRequestResult Source # | |
PluginMethod 'Request 'Method_TextDocumentFormatting Source # | |
Defined in Ide.Types handlesRequest :: SMethod 'Method_TextDocumentFormatting -> MessageParams 'Method_TextDocumentFormatting -> PluginDescriptor c -> Config -> HandleRequestResult Source # | |
PluginMethod 'Request 'Method_TextDocumentHover Source # | |
Defined in Ide.Types handlesRequest :: SMethod 'Method_TextDocumentHover -> MessageParams 'Method_TextDocumentHover -> PluginDescriptor c -> Config -> HandleRequestResult Source # | |
PluginMethod 'Request 'Method_TextDocumentPrepareCallHierarchy Source # | |
Defined in Ide.Types handlesRequest :: SMethod 'Method_TextDocumentPrepareCallHierarchy -> MessageParams 'Method_TextDocumentPrepareCallHierarchy -> PluginDescriptor c -> Config -> HandleRequestResult Source # | |
PluginMethod 'Request 'Method_TextDocumentPrepareRename Source # | |
Defined in Ide.Types handlesRequest :: SMethod 'Method_TextDocumentPrepareRename -> MessageParams 'Method_TextDocumentPrepareRename -> PluginDescriptor c -> Config -> HandleRequestResult Source # | |
PluginMethod 'Request 'Method_TextDocumentRangeFormatting Source # | |
Defined in Ide.Types handlesRequest :: SMethod 'Method_TextDocumentRangeFormatting -> MessageParams 'Method_TextDocumentRangeFormatting -> PluginDescriptor c -> Config -> HandleRequestResult Source # | |
PluginMethod 'Request 'Method_TextDocumentReferences Source # | |
Defined in Ide.Types handlesRequest :: SMethod 'Method_TextDocumentReferences -> MessageParams 'Method_TextDocumentReferences -> PluginDescriptor c -> Config -> HandleRequestResult Source # | |
PluginMethod 'Request 'Method_TextDocumentRename Source # | |
Defined in Ide.Types handlesRequest :: SMethod 'Method_TextDocumentRename -> MessageParams 'Method_TextDocumentRename -> PluginDescriptor c -> Config -> HandleRequestResult Source # | |
PluginMethod 'Request 'Method_TextDocumentSelectionRange Source # | |
Defined in Ide.Types handlesRequest :: SMethod 'Method_TextDocumentSelectionRange -> MessageParams 'Method_TextDocumentSelectionRange -> PluginDescriptor c -> Config -> HandleRequestResult Source # | |
PluginMethod 'Request 'Method_TextDocumentSemanticTokensFull Source # | |
Defined in Ide.Types handlesRequest :: SMethod 'Method_TextDocumentSemanticTokensFull -> MessageParams 'Method_TextDocumentSemanticTokensFull -> PluginDescriptor c -> Config -> HandleRequestResult Source # | |
PluginMethod 'Request 'Method_TextDocumentSemanticTokensFullDelta Source # | |
Defined in Ide.Types handlesRequest :: SMethod 'Method_TextDocumentSemanticTokensFullDelta -> MessageParams 'Method_TextDocumentSemanticTokensFullDelta -> PluginDescriptor c -> Config -> HandleRequestResult Source # | |
PluginMethod 'Request 'Method_TextDocumentTypeDefinition Source # | |
Defined in Ide.Types handlesRequest :: SMethod 'Method_TextDocumentTypeDefinition -> MessageParams 'Method_TextDocumentTypeDefinition -> PluginDescriptor c -> Config -> HandleRequestResult Source # | |
PluginMethod 'Request 'Method_WorkspaceExecuteCommand Source # | |
Defined in Ide.Types handlesRequest :: SMethod 'Method_WorkspaceExecuteCommand -> MessageParams 'Method_WorkspaceExecuteCommand -> PluginDescriptor c -> Config -> HandleRequestResult Source # | |
PluginMethod 'Request 'Method_WorkspaceSymbol Source # | |
Defined in Ide.Types handlesRequest :: SMethod 'Method_WorkspaceSymbol -> MessageParams 'Method_WorkspaceSymbol -> PluginDescriptor c -> Config -> HandleRequestResult Source # | |
PluginMethod 'Request ('Method_CustomMethod m :: Method 'ClientToServer 'Request) Source # | |
Defined in Ide.Types handlesRequest :: SMethod ('Method_CustomMethod m) -> MessageParams ('Method_CustomMethod m) -> PluginDescriptor c -> Config -> HandleRequestResult Source # |
type PluginMethodHandler a m = a -> PluginId -> MessageParams m -> ExceptT PluginError (HandlerM Config) (MessageResult m) Source #
newtype PluginNotificationHandler a (m :: Method ClientToServer Notification) Source #
PluginNotificationHandler (PluginId -> a -> VFS -> MessageParams m -> LspM Config ()) |
mkPluginNotificationHandler :: PluginNotificationMethod m => SClientMethod (m :: Method ClientToServer Notification) -> PluginNotificationMethodHandler ideState m -> PluginNotificationHandlers ideState Source #
Make a handler for plugins with no extra data
newtype PluginNotificationHandlers a Source #
Instances
Monoid (PluginNotificationHandlers a) Source # | |
Defined in Ide.Types | |
Semigroup (PluginNotificationHandlers a) Source # | |
Defined in Ide.Types (<>) :: PluginNotificationHandlers a -> PluginNotificationHandlers a -> PluginNotificationHandlers a # sconcat :: NonEmpty (PluginNotificationHandlers a) -> PluginNotificationHandlers a # stimes :: Integral b => b -> PluginNotificationHandlers a -> PluginNotificationHandlers a # |
class PluginMethod Request m => PluginRequestMethod (m :: Method ClientToServer Request) where Source #
Nothing
:: SMethod m | |
-> Config | IDE Configuration |
-> ClientCapabilities | |
-> MessageParams m | |
-> NonEmpty (MessageResult m) | |
-> MessageResult m |
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 instead allow to define how to merge two hover request responses into one glorious hover box.
However, as 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).
Instances
PluginRequestMethod 'Method_CallHierarchyIncomingCalls Source # | |
PluginRequestMethod 'Method_CallHierarchyOutgoingCalls Source # | |
PluginRequestMethod 'Method_CodeActionResolve Source # | |
PluginRequestMethod 'Method_CodeLensResolve Source # | |
PluginRequestMethod 'Method_CompletionItemResolve Source # | |
PluginRequestMethod 'Method_TextDocumentCodeAction Source # | |
PluginRequestMethod 'Method_TextDocumentCodeLens Source # | |
PluginRequestMethod 'Method_TextDocumentCompletion Source # | |
PluginRequestMethod 'Method_TextDocumentDefinition Source # | |
PluginRequestMethod 'Method_TextDocumentDocumentHighlight Source # | |
Defined in Ide.Types combineResponses :: SMethod 'Method_TextDocumentDocumentHighlight -> Config -> ClientCapabilities -> MessageParams 'Method_TextDocumentDocumentHighlight -> NonEmpty (MessageResult 'Method_TextDocumentDocumentHighlight) -> MessageResult 'Method_TextDocumentDocumentHighlight Source # | |
PluginRequestMethod 'Method_TextDocumentDocumentSymbol Source # | |
PluginRequestMethod 'Method_TextDocumentFoldingRange Source # | |
PluginRequestMethod 'Method_TextDocumentFormatting Source # | |
PluginRequestMethod 'Method_TextDocumentHover Source # | |
PluginRequestMethod 'Method_TextDocumentPrepareCallHierarchy Source # | |
Defined in Ide.Types combineResponses :: SMethod 'Method_TextDocumentPrepareCallHierarchy -> Config -> ClientCapabilities -> MessageParams 'Method_TextDocumentPrepareCallHierarchy -> NonEmpty (MessageResult 'Method_TextDocumentPrepareCallHierarchy) -> MessageResult 'Method_TextDocumentPrepareCallHierarchy Source # | |
PluginRequestMethod 'Method_TextDocumentPrepareRename Source # | |
PluginRequestMethod 'Method_TextDocumentRangeFormatting Source # | |
PluginRequestMethod 'Method_TextDocumentReferences Source # | |
PluginRequestMethod 'Method_TextDocumentRename Source # | |
PluginRequestMethod 'Method_TextDocumentSelectionRange Source # | |
PluginRequestMethod 'Method_TextDocumentSemanticTokensFull Source # | |
Defined in Ide.Types combineResponses :: SMethod 'Method_TextDocumentSemanticTokensFull -> Config -> ClientCapabilities -> MessageParams 'Method_TextDocumentSemanticTokensFull -> NonEmpty (MessageResult 'Method_TextDocumentSemanticTokensFull) -> MessageResult 'Method_TextDocumentSemanticTokensFull Source # | |
PluginRequestMethod 'Method_TextDocumentSemanticTokensFullDelta Source # | |
Defined in Ide.Types combineResponses :: SMethod 'Method_TextDocumentSemanticTokensFullDelta -> Config -> ClientCapabilities -> MessageParams 'Method_TextDocumentSemanticTokensFullDelta -> NonEmpty (MessageResult 'Method_TextDocumentSemanticTokensFullDelta) -> MessageResult 'Method_TextDocumentSemanticTokensFullDelta Source # | |
PluginRequestMethod 'Method_TextDocumentTypeDefinition Source # | |
PluginRequestMethod 'Method_WorkspaceSymbol Source # | |
PluginRequestMethod ('Method_CustomMethod m :: Method 'ClientToServer 'Request) Source # | |
getProcessID :: IO Int Source #
Get the operating system process id for the running server instance. This should be the same for the lifetime of the instance, and different from that of any other currently running instance.
installSigUsr1Handler :: IO () -> IO () Source #
$sel:lookupCommandProvider:IdePlugins_ :: IdePlugins ideState -> CommandId -> Maybe PluginId Source #
type ResolveFunction ideState a (m :: Method ClientToServer Request) = ideState -> PluginId -> MessageParams m -> Uri -> a -> ExceptT PluginError (HandlerM Config) (MessageResult m) Source #
mkResolveHandler :: forall ideState a m. (FromJSON a, PluginRequestMethod m, HasData_ (MessageParams m) (Maybe Value)) => SClientMethod m -> ResolveFunction ideState a m -> PluginHandlers ideState Source #
Make a handler for resolve methods. In here we take your provided ResolveFunction and turn it into a PluginHandlers. See Note [Resolve in PluginHandlers]