hls-plugin-api-1.6.0.0: Haskell Language Server API for plugin communication
Safe HaskellSafe-Inferred
LanguageHaskell2010

Ide.Types

Synopsis

Documentation

data PluginDescriptor (ideState :: *) Source #

Constructors

PluginDescriptor 

Fields

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 #

Constructors

IdeCommand (state -> IO ()) 

Instances

Instances details
Show (IdeCommand st) Source # 
Instance details

Defined in Ide.Types

Methods

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

Constructors

PluginRequestMethod m => IdeMethod (SMethod m) 

Instances

Instances details
GCompare IdeMethod Source # 
Instance details

Defined in Ide.Types

Methods

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

GEq IdeMethod Source # 
Instance details

Defined in Ide.Types

Methods

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

data IdeNotification (m :: Method FromClient Notification) Source #

Methods which have a PluginMethod instance

Constructors

PluginNotificationMethod m => IdeNotification (SMethod m) 

Instances

Instances details
GCompare IdeNotification Source # 
Instance details

Defined in Ide.Types

Methods

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

GEq IdeNotification Source # 
Instance details

Defined in Ide.Types

Methods

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

data IdePlugins ideState where Source #

Bundled Patterns

pattern IdePlugins :: [PluginDescriptor ideState] -> IdePlugins ideState

Smart constructor that deduplicates plugins

Instances

Instances details
Monoid (IdePlugins a) Source # 
Instance details

Defined in Ide.Types

Semigroup (IdePlugins a) Source # 
Instance details

Defined in Ide.Types

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.

Constructors

DynFlagsModifications 

Fields

data Config Source #

We (initially anyway) mirror the hie configuration, so that existing clients can simply switch executable and not have any nasty surprises. There will be surprises relating to config options being ignored, initially though.

Instances

Instances details
ToJSON Config Source # 
Instance details

Defined in Ide.Types

Show Config Source # 
Instance details

Defined in Ide.Types

Default Config Source # 
Instance details

Defined in Ide.Types

Methods

def :: Config #

Eq Config Source # 
Instance details

Defined in Ide.Types

Methods

(==) :: Config -> Config -> Bool #

(/=) :: Config -> Config -> Bool #

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.

Instances

Instances details
ToJSON PluginConfig Source # 
Instance details

Defined in Ide.Types

Show PluginConfig Source # 
Instance details

Defined in Ide.Types

Default PluginConfig Source # 
Instance details

Defined in Ide.Types

Methods

def :: PluginConfig #

Eq PluginConfig Source # 
Instance details

Defined in Ide.Types

data CheckParents Source #

Instances

Instances details
FromJSON CheckParents Source # 
Instance details

Defined in Ide.Types

ToJSON CheckParents Source # 
Instance details

Defined in Ide.Types

Generic CheckParents Source # 
Instance details

Defined in Ide.Types

Associated Types

type Rep CheckParents :: Type -> Type #

Show CheckParents Source # 
Instance details

Defined in Ide.Types

Eq CheckParents Source # 
Instance details

Defined in Ide.Types

Ord CheckParents Source # 
Instance details

Defined in Ide.Types

type Rep CheckParents Source # 
Instance details

Defined in Ide.Types

type Rep CheckParents = D1 ('MetaData "CheckParents" "Ide.Types" "hls-plugin-api-1.6.0.0-FBBe7YX7CAV7fcO2QVUIWy" 'False) (C1 ('MetaCons "NeverCheck" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CheckOnSave" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AlwaysCheck" 'PrefixI 'False) (U1 :: Type -> Type)))

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.

Constructors

ConfigDescriptor 

Fields

configForPlugin :: Config -> PluginDescriptor c -> PluginConfig Source #

Lookup the current config for a plugin

pluginEnabledConfig :: (PluginConfig -> Bool) -> PluginConfig -> Bool Source #

Checks that a given plugin is both enabled and the specific feature is enabled

data CustomConfig Source #

An existential wrapper of Properties

Constructors

forall r. CustomConfig (Properties r) 

data FallbackCodeActionParams Source #

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.

class HasTracing a where Source #

Minimal complete definition

Nothing

Methods

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

Instances

Instances details
HasTracing Value Source # 
Instance details

Defined in Ide.Types

HasTracing CallHierarchyIncomingCallsParams Source # 
Instance details

Defined in Ide.Types

HasTracing CallHierarchyOutgoingCallsParams Source # 
Instance details

Defined in Ide.Types

HasTracing ExecuteCommandParams Source # 
Instance details

Defined in Ide.Types

HasTracing CompletionItem Source # 
Instance details

Defined in Ide.Types

HasTracing DidChangeConfigurationParams Source # 
Instance details

Defined in Ide.Types

HasTracing InitializeParams Source # 
Instance details

Defined in Ide.Types

HasTracing DidChangeWatchedFilesParams Source # 
Instance details

Defined in Ide.Types

HasTracing DidChangeWorkspaceFoldersParams Source # 
Instance details

Defined in Ide.Types

HasTracing WorkspaceSymbolParams Source # 
Instance details

Defined in Ide.Types

(HasTextDocument a doc, HasUri doc Uri) => HasTracing a Source # 
Instance details

Defined in Ide.Types

Methods

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

HasTracing (Maybe InitializedParams) Source # 
Instance details

Defined in Ide.Types

data PluginCommand ideState Source #

Constructors

forall a.FromJSON a => PluginCommand 

newtype CommandId Source #

Constructors

CommandId Text 

Instances

Instances details
IsString 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

Eq CommandId Source # 
Instance details

Defined in Ide.Types

Ord CommandId Source # 
Instance details

Defined in Ide.Types

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

newtype PluginId Source #

Constructors

PluginId Text 

Instances

Instances details
FromJSON PluginId Source # 
Instance details

Defined in Ide.Types

IsString 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

Eq PluginId Source # 
Instance details

Defined in Ide.Types

Ord PluginId Source # 
Instance details

Defined in Ide.Types

Hashable PluginId Source # 
Instance details

Defined in Ide.Types

Methods

hashWithSalt :: Int -> PluginId -> Int #

hash :: PluginId -> Int #

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

Combine handlers for the

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

Make a handler for plugins with no extra data

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

Minimal complete definition

Nothing

Methods

pluginEnabled Source #

Arguments

:: 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?

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.

Instances

Instances details
PluginMethod 'Notification 'Initialized Source # 
Instance details

Defined in Ide.Types

PluginMethod 'Notification 'TextDocumentDidChange Source # 
Instance details

Defined in Ide.Types

PluginMethod 'Notification 'TextDocumentDidClose Source # 
Instance details

Defined in Ide.Types

PluginMethod 'Notification 'TextDocumentDidOpen Source # 
Instance details

Defined in Ide.Types

PluginMethod 'Notification 'TextDocumentDidSave Source # 
Instance details

Defined in Ide.Types

PluginMethod 'Notification 'WorkspaceDidChangeConfiguration Source # 
Instance details

Defined in Ide.Types

PluginMethod 'Notification 'WorkspaceDidChangeWatchedFiles Source # 
Instance details

Defined in Ide.Types

PluginMethod 'Notification 'WorkspaceDidChangeWorkspaceFolders Source # 
Instance details

Defined in Ide.Types

PluginMethod 'Request 'CallHierarchyIncomingCalls Source # 
Instance details

Defined in Ide.Types

PluginMethod 'Request 'CallHierarchyOutgoingCalls Source # 
Instance details

Defined in Ide.Types

PluginMethod 'Request 'CompletionItemResolve Source # 
Instance details

Defined in Ide.Types

PluginMethod 'Request 'TextDocumentCodeAction Source # 
Instance details

Defined in Ide.Types

PluginMethod 'Request 'TextDocumentCodeLens Source # 
Instance details

Defined in Ide.Types

PluginMethod 'Request 'TextDocumentCompletion Source # 
Instance details

Defined in Ide.Types

PluginMethod 'Request 'TextDocumentDefinition Source # 
Instance details

Defined in Ide.Types

PluginMethod 'Request 'TextDocumentDocumentHighlight Source # 
Instance details

Defined in Ide.Types

PluginMethod 'Request 'TextDocumentDocumentSymbol Source # 
Instance details

Defined in Ide.Types

PluginMethod 'Request 'TextDocumentFoldingRange Source # 
Instance details

Defined in Ide.Types

PluginMethod 'Request 'TextDocumentFormatting Source # 
Instance details

Defined in Ide.Types

PluginMethod 'Request 'TextDocumentHover Source # 
Instance details

Defined in Ide.Types

PluginMethod 'Request 'TextDocumentPrepareCallHierarchy Source # 
Instance details

Defined in Ide.Types

PluginMethod 'Request 'TextDocumentRangeFormatting Source # 
Instance details

Defined in Ide.Types

PluginMethod 'Request 'TextDocumentReferences Source # 
Instance details

Defined in Ide.Types

PluginMethod 'Request 'TextDocumentRename Source # 
Instance details

Defined in Ide.Types

PluginMethod 'Request 'TextDocumentSelectionRange Source # 
Instance details

Defined in Ide.Types

PluginMethod 'Request 'TextDocumentTypeDefinition Source # 
Instance details

Defined in Ide.Types

PluginMethod 'Request 'WorkspaceSymbol Source # 
Instance details

Defined in Ide.Types

PluginMethod 'Request ('CustomMethod :: Method 'FromClient 'Request) Source # 
Instance details

Defined in Ide.Types

mkPluginNotificationHandler :: PluginNotificationMethod m => SClientMethod (m :: Method FromClient Notification) -> PluginNotificationMethodHandler ideState m -> PluginNotificationHandlers ideState Source #

Make a handler for plugins with no extra data

class PluginMethod Request m => PluginRequestMethod (m :: Method FromClient Request) where Source #

Minimal complete definition

Nothing

Methods

combineResponses Source #

Arguments

:: 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).

Instances

Instances details
PluginRequestMethod 'CallHierarchyIncomingCalls Source # 
Instance details

Defined in Ide.Types

PluginRequestMethod 'CallHierarchyOutgoingCalls Source # 
Instance details

Defined in Ide.Types

PluginRequestMethod 'CompletionItemResolve Source # 
Instance details

Defined in Ide.Types

PluginRequestMethod 'TextDocumentCodeAction Source # 
Instance details

Defined in Ide.Types

PluginRequestMethod 'TextDocumentCodeLens Source # 
Instance details

Defined in Ide.Types

PluginRequestMethod 'TextDocumentCompletion Source # 
Instance details

Defined in Ide.Types

PluginRequestMethod 'TextDocumentDefinition Source # 
Instance details

Defined in Ide.Types

PluginRequestMethod 'TextDocumentDocumentHighlight Source # 
Instance details

Defined in Ide.Types

PluginRequestMethod 'TextDocumentDocumentSymbol Source # 
Instance details

Defined in Ide.Types

PluginRequestMethod 'TextDocumentFoldingRange Source # 
Instance details

Defined in Ide.Types

PluginRequestMethod 'TextDocumentFormatting Source # 
Instance details

Defined in Ide.Types

PluginRequestMethod 'TextDocumentHover Source # 
Instance details

Defined in Ide.Types

PluginRequestMethod 'TextDocumentPrepareCallHierarchy Source # 
Instance details

Defined in Ide.Types

PluginRequestMethod 'TextDocumentRangeFormatting Source # 
Instance details

Defined in Ide.Types

PluginRequestMethod 'TextDocumentReferences Source # 
Instance details

Defined in Ide.Types

PluginRequestMethod 'TextDocumentRename Source # 
Instance details

Defined in Ide.Types

PluginRequestMethod 'TextDocumentSelectionRange Source # 
Instance details

Defined in Ide.Types

PluginRequestMethod 'TextDocumentTypeDefinition Source # 
Instance details

Defined in Ide.Types

PluginRequestMethod 'WorkspaceSymbol Source # 
Instance details

Defined in Ide.Types

PluginRequestMethod ('CustomMethod :: Method 'FromClient 'Request) Source # 
Instance details

Defined in Ide.Types

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.