hls-plugin-api-1.0.0.0: Haskell Language Server API for plugin communication
Safe HaskellNone
LanguageHaskell2010

Ide.Types

Synopsis

Documentation

newtype IdePlugins ideState Source #

Constructors

IdePlugins 

Fields

data PluginDescriptor ideState Source #

Constructors

PluginDescriptor 

Fields

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

Minimal complete definition

pluginEnabled

Methods

pluginEnabled :: SMethod m -> PluginId -> Config -> Bool Source #

Parse the configuration to check if this plugin is enabled

combineResponses Source #

Arguments

:: SMethod m 
-> Config

IDE Configuration

-> ClientCapabilities 
-> MessageParams m 
-> NonEmpty (ResponseResult m) 
-> ResponseResult m 

How to combine responses from different plugins

Instances

Instances details
PluginMethod 'TextDocumentRename Source # 
Instance details

Defined in Ide.Types

PluginMethod 'TextDocumentRangeFormatting Source # 
Instance details

Defined in Ide.Types

PluginMethod 'TextDocumentFormatting Source # 
Instance details

Defined in Ide.Types

PluginMethod 'TextDocumentCodeLens Source # 
Instance details

Defined in Ide.Types

PluginMethod 'TextDocumentCodeAction Source # 
Instance details

Defined in Ide.Types

PluginMethod 'TextDocumentDocumentSymbol Source # 
Instance details

Defined in Ide.Types

PluginMethod 'TextDocumentHover Source # 
Instance details

Defined in Ide.Types

PluginMethod 'TextDocumentCompletion Source # 
Instance details

Defined in Ide.Types

data IdeMethod (m :: Method FromClient Request) Source #

Methods which have a PluginMethod instance

Constructors

PluginMethod m => IdeMethod (SMethod m) 

Instances

Instances details
GEq IdeMethod Source # 
Instance details

Defined in Ide.Types

Methods

geq :: forall (a :: k) (b :: k). IdeMethod a -> IdeMethod b -> Maybe (a :~: b) #

GCompare IdeMethod Source # 
Instance details

Defined in Ide.Types

Methods

gcompare :: forall (a :: k) (b :: k). IdeMethod a -> IdeMethod b -> GOrdering a b #

newtype PluginHandler a (m :: Method FromClient Request) Source #

Combine handlers for the

mkPluginHandler :: PluginMethod m => SClientMethod m -> PluginMethodHandler ideState m -> PluginHandlers ideState Source #

Make a handler for plugins with no extra data

newtype CommandId Source #

Constructors

CommandId Text 

Instances

Instances details
Eq CommandId Source # 
Instance details

Defined in Ide.Types

Ord CommandId Source # 
Instance details

Defined in Ide.Types

Read CommandId Source # 
Instance details

Defined in Ide.Types

Show CommandId Source # 
Instance details

Defined in Ide.Types

IsString CommandId Source # 
Instance details

Defined in Ide.Types

data PluginCommand ideState Source #

Constructors

forall a.FromJSON a => PluginCommand 

type CommandFunction ideState a = ideState -> a -> LspM Config (Either ResponseError Value) Source #

newtype WithSnippets Source #

Constructors

WithSnippets Bool 

newtype PluginId Source #

Constructors

PluginId Text 

Instances

Instances details
Eq PluginId Source # 
Instance details

Defined in Ide.Types

Ord PluginId Source # 
Instance details

Defined in Ide.Types

Read PluginId Source # 
Instance details

Defined in Ide.Types

Show PluginId Source # 
Instance details

Defined in Ide.Types

IsString PluginId Source # 
Instance details

Defined in Ide.Types

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.

data FallbackCodeActionParams Source #

class HasTracing a where Source #

Minimal complete definition

Nothing

Methods

traceWithSpan :: SpanInFlight -> a -> IO () Source #

getPid :: IO 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.