Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype IdePlugins ideState = IdePlugins {
- ipMap :: [(PluginId, PluginDescriptor ideState)]
- data PluginDescriptor ideState = PluginDescriptor {
- pluginId :: !PluginId
- pluginRules :: !(Rules ())
- pluginCommands :: ![PluginCommand ideState]
- pluginHandlers :: PluginHandlers ideState
- pluginCustomConfig :: CustomConfig
- pluginNotificationHandlers :: PluginNotificationHandlers ideState
- data CustomConfig = forall r. CustomConfig (Properties r)
- emptyCustomConfig :: CustomConfig
- mkCustomConfig :: Properties r -> CustomConfig
- class HasTracing (MessageParams m) => PluginMethod m where
- pluginEnabled :: SMethod m -> PluginId -> Config -> Bool
- combineResponses :: SMethod m -> Config -> ClientCapabilities -> MessageParams m -> NonEmpty (ResponseResult m) -> ResponseResult m
- data IdeMethod (m :: Method FromClient Request) = PluginMethod m => IdeMethod (SMethod m)
- data IdeNotification (m :: Method FromClient Notification) = HasTracing (MessageParams m) => IdeNotification (SMethod m)
- newtype PluginHandler a (m :: Method FromClient Request) = PluginHandler (PluginId -> a -> MessageParams m -> LspM Config (NonEmpty (Either ResponseError (ResponseResult m))))
- newtype PluginNotificationHandler a (m :: Method FromClient Notification) = PluginNotificationHandler (PluginId -> a -> MessageParams m -> LspM Config ())
- newtype PluginHandlers a = PluginHandlers (DMap IdeMethod (PluginHandler a))
- newtype PluginNotificationHandlers a = PluginNotificationHandlers (DMap IdeNotification (PluginNotificationHandler a))
- type PluginMethodHandler a m = a -> PluginId -> MessageParams m -> LspM Config (Either ResponseError (ResponseResult m))
- type PluginNotificationMethodHandler a m = a -> PluginId -> MessageParams m -> LspM Config ()
- mkPluginHandler :: PluginMethod m => SClientMethod m -> PluginMethodHandler ideState m -> PluginHandlers ideState
- mkPluginNotificationHandler :: HasTracing (MessageParams m) => SClientMethod (m :: Method FromClient Notification) -> PluginNotificationMethodHandler ideState m -> PluginNotificationHandlers ideState
- defaultPluginDescriptor :: PluginId -> PluginDescriptor ideState
- newtype CommandId = CommandId Text
- data PluginCommand ideState = forall a.FromJSON a => PluginCommand {
- commandId :: CommandId
- commandDesc :: Text
- commandFunc :: CommandFunction ideState a
- type CommandFunction ideState a = ideState -> a -> LspM Config (Either ResponseError Value)
- newtype PluginId = PluginId Text
- configForPlugin :: Config -> PluginId -> PluginConfig
- pluginEnabledConfig :: (PluginConfig -> Bool) -> PluginId -> Config -> Bool
- 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
- responseError :: Text -> ResponseError
- data FallbackCodeActionParams = FallbackCodeActionParams {}
- otSetUri :: SpanInFlight -> Uri -> IO ()
- class HasTracing a where
- traceWithSpan :: SpanInFlight -> a -> IO ()
- pROCESS_ID :: Text
- mkLspCommand :: PluginId -> CommandId -> Text -> Maybe [Value] -> Command
- mkLspCmdId :: Text -> PluginId -> CommandId -> Text
- getPid :: IO Text
- getProcessID :: IO Int
- installSigUsr1Handler :: IO () -> IO ()
Documentation
newtype IdePlugins ideState Source #
IdePlugins | |
|
data PluginDescriptor ideState Source #
PluginDescriptor | |
|
data CustomConfig Source #
An existential wrapper of Properties
, used only for documenting and generating config templates
forall r. CustomConfig (Properties r) |
mkCustomConfig :: Properties r -> CustomConfig Source #
class HasTracing (MessageParams m) => PluginMethod m 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
pluginEnabled :: SMethod m -> PluginId -> Config -> Bool Source #
Parse the configuration to check if this plugin is enabled
:: SMethod m | |
-> Config | IDE Configuration |
-> ClientCapabilities | |
-> MessageParams m | |
-> NonEmpty (ResponseResult m) | |
-> ResponseResult m |
How to combine responses from different plugins
default combineResponses :: Semigroup (ResponseResult m) => SMethod m -> Config -> ClientCapabilities -> MessageParams m -> NonEmpty (ResponseResult m) -> ResponseResult m Source #
Instances
data IdeMethod (m :: Method FromClient Request) Source #
Methods which have a PluginMethod instance
PluginMethod m => IdeMethod (SMethod m) |
data IdeNotification (m :: Method FromClient Notification) Source #
Methods which have a PluginMethod instance
HasTracing (MessageParams m) => IdeNotification (SMethod m) |
Instances
GEq IdeNotification Source # | |
Defined in Ide.Types geq :: forall (a :: k) (b :: k). IdeNotification a -> IdeNotification b -> Maybe (a :~: b) # | |
GCompare IdeNotification Source # | |
Defined in Ide.Types gcompare :: forall (a :: k) (b :: k). IdeNotification a -> IdeNotification b -> GOrdering a b # |
newtype PluginHandler a (m :: Method FromClient Request) Source #
Combine handlers for the
PluginHandler (PluginId -> a -> MessageParams m -> LspM Config (NonEmpty (Either ResponseError (ResponseResult m)))) |
newtype PluginNotificationHandler a (m :: Method FromClient Notification) Source #
PluginNotificationHandler (PluginId -> a -> MessageParams m -> LspM Config ()) |
newtype PluginHandlers a Source #
Instances
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 # | |
Monoid (PluginHandlers a) Source # | |
Defined in Ide.Types mempty :: PluginHandlers a # mappend :: PluginHandlers a -> PluginHandlers a -> PluginHandlers a # mconcat :: [PluginHandlers a] -> PluginHandlers a # |
newtype PluginNotificationHandlers a Source #
Instances
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 # | |
Monoid (PluginNotificationHandlers a) Source # | |
Defined in Ide.Types |
type PluginMethodHandler a m = a -> PluginId -> MessageParams m -> LspM Config (Either ResponseError (ResponseResult m)) Source #
type PluginNotificationMethodHandler a m = a -> PluginId -> MessageParams m -> LspM Config () Source #
mkPluginHandler :: PluginMethod m => SClientMethod m -> PluginMethodHandler ideState m -> PluginHandlers ideState Source #
Make a handler for plugins with no extra data
mkPluginNotificationHandler :: HasTracing (MessageParams m) => SClientMethod (m :: Method FromClient Notification) -> PluginNotificationMethodHandler ideState m -> PluginNotificationHandlers ideState Source #
Make a handler for plugins with no extra data
defaultPluginDescriptor :: PluginId -> PluginDescriptor ideState Source #
data PluginCommand ideState Source #
forall a.FromJSON a => PluginCommand | |
|
type CommandFunction ideState a = ideState -> a -> LspM Config (Either ResponseError Value) Source #
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
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 #
responseError :: Text -> ResponseError Source #
data FallbackCodeActionParams Source #
Instances
Generic FallbackCodeActionParams Source # | |
ToJSON FallbackCodeActionParams Source # | |
Defined in Ide.Types | |
FromJSON FallbackCodeActionParams Source # | |
Defined in Ide.Types | |
type Rep FallbackCodeActionParams Source # | |
Defined in Ide.Types type Rep FallbackCodeActionParams = D1 ('MetaData "FallbackCodeActionParams" "Ide.Types" "hls-plugin-api-1.1.0.0-EHF0TaHL0RO244P4RRI1vx" '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)))) |
class HasTracing a where Source #
Nothing
traceWithSpan :: SpanInFlight -> a -> IO () Source #
Instances
pROCESS_ID :: Text 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.
getProcessID :: IO Int Source #
installSigUsr1Handler :: IO () -> IO () Source #