Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data PluginDescriptor (ideState :: *) = PluginDescriptor {
- pluginId :: !PluginId
- 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 -> PluginDescriptor ideState
- defaultCabalPluginDescriptor :: PluginId -> PluginDescriptor ideState
- defaultPluginPriority :: Natural
- newtype IdeCommand state = IdeCommand (state -> IO ())
- data IdeMethod (m :: Method FromClient Request) = PluginRequestMethod m => IdeMethod (SMethod m)
- data IdeNotification (m :: Method FromClient Notification) = PluginNotificationMethod m => IdeNotification (SMethod m)
- data IdePlugins ideState where
- pattern IdePlugins :: [PluginDescriptor ideState] -> IdePlugins ideState
- data DynFlagsModifications = DynFlagsModifications {}
- data ConfigDescriptor = ConfigDescriptor {}
- defaultConfigDescriptor :: ConfigDescriptor
- configForPlugin :: Config -> PluginId -> PluginConfig
- pluginEnabledConfig :: (PluginConfig -> Bool) -> PluginId -> Config -> Bool
- data CustomConfig = forall r. CustomConfig (Properties r)
- mkCustomConfig :: Properties r -> CustomConfig
- data FallbackCodeActionParams = FallbackCodeActionParams {}
- data FormattingType
- type FormattingMethod m = (HasOptions (MessageParams m) FormattingOptions, HasTextDocument (MessageParams m) TextDocumentIdentifier, ResponseResult m ~ List TextEdit)
- type FormattingHandler a = a -> FormattingType -> Text -> NormalizedFilePath -> FormattingOptions -> LspM Config (Either ResponseError (List TextEdit))
- 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 -> a -> LspM Config (Either ResponseError Value)
- mkLspCommand :: PluginId -> CommandId -> Text -> Maybe [Value] -> Command
- mkLspCmdId :: Text -> PluginId -> CommandId -> Text
- newtype PluginId = PluginId Text
- newtype PluginHandler a (m :: Method FromClient Request) = PluginHandler (PluginId -> a -> MessageParams m -> LspM Config (NonEmpty (Either ResponseError (ResponseResult m))))
- mkPluginHandler :: PluginRequestMethod m => SClientMethod m -> PluginMethodHandler ideState m -> PluginHandlers ideState
- newtype PluginHandlers a = PluginHandlers (DMap IdeMethod (PluginHandler a))
- class HasTracing (MessageParams m) => PluginMethod (k :: MethodType) (m :: Method FromClient k) where
- pluginEnabled :: SMethod m -> MessageParams m -> PluginDescriptor c -> Config -> Bool
- type PluginMethodHandler a m = a -> PluginId -> MessageParams m -> LspM Config (Either ResponseError (ResponseResult m))
- newtype PluginNotificationHandler a (m :: Method FromClient Notification) = PluginNotificationHandler (PluginId -> a -> VFS -> MessageParams m -> LspM Config ())
- mkPluginNotificationHandler :: PluginNotificationMethod m => SClientMethod (m :: Method FromClient Notification) -> PluginNotificationMethodHandler ideState m -> PluginNotificationHandlers ideState
- newtype PluginNotificationHandlers a = PluginNotificationHandlers (DMap IdeNotification (PluginNotificationHandler a))
- class PluginMethod Request m => PluginRequestMethod (m :: Method FromClient Request) where
- combineResponses :: SMethod m -> Config -> ClientCapabilities -> MessageParams m -> NonEmpty (ResponseResult m) -> ResponseResult m
- getProcessID :: IO Int
- getPid :: IO Text
- installSigUsr1Handler :: IO () -> IO ()
- responseError :: Text -> ResponseError
- lookupCommandProvider :: IdePlugins ideState -> CommandId -> Maybe PluginId
Documentation
data PluginDescriptor (ideState :: *) Source #
PluginDescriptor | |
|
defaultPluginDescriptor :: PluginId -> PluginDescriptor ideState Source #
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.
defaultCabalPluginDescriptor :: PluginId -> PluginDescriptor ideState Source #
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
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 FromClient Request) Source #
Methods which have a PluginMethod instance
PluginRequestMethod m => IdeMethod (SMethod m) |
data IdeNotification (m :: Method FromClient 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
pluginModifyDynflags
in their PluginDescriptor
.
DynFlagsModifications | |
|
Instances
Monoid DynFlagsModifications Source # | |
Defined in Ide.Types | |
Semigroup DynFlagsModifications Source # | |
Defined in Ide.Types |
data ConfigDescriptor Source #
Describes the configuration a plugin. A plugin may be configurable in such form:
{ "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 -> PluginId -> PluginConfig Source #
pluginEnabledConfig :: (PluginConfig -> Bool) -> PluginId -> Config -> Bool Source #
Checks that a given plugin is both enabled and the specific feature is enabled
mkCustomConfig :: Properties r -> CustomConfig Source #
data FallbackCodeActionParams Source #
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-1.5.0.0-BXQtiafHCTK9l5i8ZO3ecW" '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.
type FormattingMethod m = (HasOptions (MessageParams m) FormattingOptions, HasTextDocument (MessageParams m) TextDocumentIdentifier, ResponseResult m ~ List TextEdit) Source #
type FormattingHandler a = a -> FormattingType -> Text -> NormalizedFilePath -> FormattingOptions -> LspM Config (Either ResponseError (List TextEdit)) Source #
mkFormattingHandlers :: forall a. FormattingHandler a -> PluginHandlers a Source #
class HasTracing a where Source #
Nothing
traceWithSpan :: SpanInFlight -> a -> IO () Source #
Instances
data PluginCommand ideState Source #
forall a.FromJSON a => PluginCommand | |
|
type CommandFunction ideState a = ideState -> a -> LspM Config (Either ResponseError Value) Source #
newtype PluginHandler a (m :: Method FromClient Request) Source #
Combine handlers for the
PluginHandler (PluginId -> a -> MessageParams m -> LspM Config (NonEmpty (Either ResponseError (ResponseResult m)))) |
mkPluginHandler :: PluginRequestMethod m => SClientMethod m -> PluginMethodHandler ideState m -> PluginHandlers ideState Source #
Make a handler for plugins with no extra data
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 :: MethodType) (m :: Method FromClient 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
eg |
-> 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 |
-> Bool | 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 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 HLS knows plugins specific for Haskell and specific for Cabal file descriptions
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.
default pluginEnabled :: (HasTextDocument (MessageParams m) doc, HasUri doc Uri) => SMethod m -> MessageParams m -> PluginDescriptor c -> Config -> Bool Source #
Instances
type PluginMethodHandler a m = a -> PluginId -> MessageParams m -> LspM Config (Either ResponseError (ResponseResult m)) Source #
newtype PluginNotificationHandler a (m :: Method FromClient Notification) Source #
PluginNotificationHandler (PluginId -> a -> VFS -> MessageParams m -> LspM Config ()) |
mkPluginNotificationHandler :: PluginNotificationMethod m => SClientMethod (m :: Method FromClient 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 FromClient Request) where Source #
Nothing
:: SMethod m | |
-> Config | IDE Configuration |
-> ClientCapabilities | |
-> MessageParams m | |
-> NonEmpty (ResponseResult m) | |
-> ResponseResult 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 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).
default combineResponses :: Semigroup (ResponseResult m) => SMethod m -> Config -> ClientCapabilities -> MessageParams m -> NonEmpty (ResponseResult m) -> ResponseResult m Source #
Instances
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 #
responseError :: Text -> ResponseError Source #
lookupCommandProvider :: IdePlugins ideState -> CommandId -> Maybe PluginId Source #