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

Ide.Types

Synopsis

Documentation

data PluginDescriptor (ideState :: Type) #

Constructors

PluginDescriptor 

Fields

defaultPluginDescriptor :: PluginId -> PluginDescriptor ideState #

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 -> PluginDescriptor ideState #

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

newtype IdeCommand state #

Constructors

IdeCommand (state -> IO ()) 

Instances

Instances details
Show (IdeCommand st) # 
Instance details

Defined in Ide.Types

Methods

showsPrec :: Int -> IdeCommand st -> ShowS #

show :: IdeCommand st -> String #

showList :: [IdeCommand st] -> ShowS #

data IdeMethod (m :: Method ClientToServer Request) #

Methods which have a PluginMethod instance

Constructors

PluginRequestMethod m => IdeMethod (SMethod m) 

Instances

Instances details
GCompare IdeMethod # 
Instance details

Defined in Ide.Types

Methods

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

GEq IdeMethod # 
Instance details

Defined in Ide.Types

Methods

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

data IdeNotification (m :: Method ClientToServer Notification) #

Methods which have a PluginMethod instance

Constructors

PluginNotificationMethod m => IdeNotification (SMethod m) 

Instances

Instances details
GCompare IdeNotification # 
Instance details

Defined in Ide.Types

Methods

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

GEq IdeNotification # 
Instance details

Defined in Ide.Types

Methods

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

data IdePlugins ideState where #

Bundled Patterns

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

Smart constructor that deduplicates plugins

Instances

Instances details
Monoid (IdePlugins a) # 
Instance details

Defined in Ide.Types

Semigroup (IdePlugins a) # 
Instance details

Defined in Ide.Types

Methods

(<>) :: IdePlugins a -> IdePlugins a -> IdePlugins a #

sconcat :: NonEmpty (IdePlugins a) -> IdePlugins a #

stimes :: Integral b => b -> IdePlugins a -> IdePlugins a #

data DynFlagsModifications #

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

  • dynFlagsModifyGlobal :: DynFlags -> DynFlags

    Invoked immediately at the package level. Changes to the DynFlags made in dynFlagsModifyGlobal are guaranteed to be seen everywhere in the compilation pipeline.

  • dynFlagsModifyParser :: DynFlags -> DynFlags

    Invoked just before the parsing step, and reset immediately afterwards. dynFlagsModifyParser allows plugins to enable language extensions only during parsing. for example, to let them enable certain pieces of syntax.

data Config #

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.

Instances

Instances details
ToJSON Config # 
Instance details

Defined in Ide.Types

Show Config # 
Instance details

Defined in Ide.Types

Methods

showsPrec :: Int -> Config -> ShowS #

show :: Config -> String #

showList :: [Config] -> ShowS #

Default Config # 
Instance details

Defined in Ide.Types

Methods

def :: Config #

Eq Config # 
Instance details

Defined in Ide.Types

Methods

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

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

data PluginConfig #

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.

Constructors

PluginConfig 

Fields

Instances

Instances details
ToJSON PluginConfig # 
Instance details

Defined in Ide.Types

Show PluginConfig # 
Instance details

Defined in Ide.Types

Methods

showsPrec :: Int -> PluginConfig -> ShowS #

show :: PluginConfig -> String #

showList :: [PluginConfig] -> ShowS #

Default PluginConfig # 
Instance details

Defined in Ide.Types

Methods

def :: PluginConfig #

Eq PluginConfig # 
Instance details

Defined in Ide.Types

Methods

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

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

data CheckParents #

Instances

Instances details
FromJSON CheckParents # 
Instance details

Defined in Ide.Types

ToJSON CheckParents # 
Instance details

Defined in Ide.Types

Generic CheckParents # 
Instance details

Defined in Ide.Types

Associated Types

type Rep CheckParents :: Type -> Type

Show CheckParents # 
Instance details

Defined in Ide.Types

Methods

showsPrec :: Int -> CheckParents -> ShowS #

show :: CheckParents -> String #

showList :: [CheckParents] -> ShowS #

Eq CheckParents # 
Instance details

Defined in Ide.Types

Methods

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

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

Ord CheckParents # 
Instance details

Defined in Ide.Types

type Rep CheckParents # 
Instance details

Defined in Ide.Types

type Rep CheckParents = D1 ('MetaData "CheckParents" "Ide.Types" "hls-plugin-api-2.4.0.0-KJfNpTBJq8lII4el4H2UW6" '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 #

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.

Constructors

ConfigDescriptor 

Fields

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

Lookup the current config for a plugin

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

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

data CustomConfig #

An existential wrapper of Properties

Constructors

forall r. CustomConfig (Properties r) 

data FallbackCodeActionParams #

Instances

Instances details
FromJSON FallbackCodeActionParams # 
Instance details

Defined in Ide.Types

ToJSON FallbackCodeActionParams # 
Instance details

Defined in Ide.Types

Generic FallbackCodeActionParams # 
Instance details

Defined in Ide.Types

Associated Types

type Rep FallbackCodeActionParams :: Type -> Type

type Rep FallbackCodeActionParams # 
Instance details

Defined in Ide.Types

type Rep FallbackCodeActionParams = D1 ('MetaData "FallbackCodeActionParams" "Ide.Types" "hls-plugin-api-2.4.0.0-KJfNpTBJq8lII4el4H2UW6" '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 #

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 #

Minimal complete definition

Nothing

Methods

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

Instances

Instances details
HasTracing Value # 
Instance details

Defined in Ide.Types

Methods

traceWithSpan :: SpanInFlight -> Value -> IO () #

HasTracing CallHierarchyIncomingCallsParams # 
Instance details

Defined in Ide.Types

HasTracing CallHierarchyOutgoingCallsParams # 
Instance details

Defined in Ide.Types

HasTracing CodeAction # 
Instance details

Defined in Ide.Types

Methods

traceWithSpan :: SpanInFlight -> CodeAction -> IO () #

HasTracing CodeLens # 
Instance details

Defined in Ide.Types

Methods

traceWithSpan :: SpanInFlight -> CodeLens -> IO () #

HasTracing CompletionItem # 
Instance details

Defined in Ide.Types

HasTracing DidChangeConfigurationParams # 
Instance details

Defined in Ide.Types

HasTracing DidChangeWatchedFilesParams # 
Instance details

Defined in Ide.Types

HasTracing DidChangeWorkspaceFoldersParams # 
Instance details

Defined in Ide.Types

HasTracing DocumentLink # 
Instance details

Defined in Ide.Types

HasTracing ExecuteCommandParams # 
Instance details

Defined in Ide.Types

HasTracing InitializeParams # 
Instance details

Defined in Ide.Types

HasTracing InitializedParams # 
Instance details

Defined in Ide.Types

HasTracing InlayHint # 
Instance details

Defined in Ide.Types

Methods

traceWithSpan :: SpanInFlight -> InlayHint -> IO () #

HasTracing WorkspaceSymbol # 
Instance details

Defined in Ide.Types

HasTracing WorkspaceSymbolParams # 
Instance details

Defined in Ide.Types

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

Defined in Ide.Types

Methods

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

data PluginCommand ideState #

Constructors

forall a.FromJSON a => PluginCommand 

newtype CommandId #

Constructors

CommandId Text 

Instances

Instances details
IsString CommandId # 
Instance details

Defined in Ide.Types

Read CommandId # 
Instance details

Defined in Ide.Types

Methods

readsPrec :: Int -> ReadS CommandId #

readList :: ReadS [CommandId] #

readPrec :: ReadPrec CommandId #

readListPrec :: ReadPrec [CommandId] #

Show CommandId # 
Instance details

Defined in Ide.Types

Methods

showsPrec :: Int -> CommandId -> ShowS #

show :: CommandId -> String #

showList :: [CommandId] -> ShowS #

Eq CommandId # 
Instance details

Defined in Ide.Types

Methods

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

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

Ord CommandId # 
Instance details

Defined in Ide.Types

Methods

compare :: CommandId -> CommandId -> Ordering

(<) :: CommandId -> CommandId -> Bool

(<=) :: CommandId -> CommandId -> Bool

(>) :: CommandId -> CommandId -> Bool

(>=) :: CommandId -> CommandId -> Bool

max :: CommandId -> CommandId -> CommandId

min :: CommandId -> CommandId -> CommandId

type CommandFunction ideState a = ideState -> a -> ExceptT PluginError (LspM Config) (Value |? Null) #

newtype PluginId #

Constructors

PluginId Text 

Instances

Instances details
FromJSON PluginId # 
Instance details

Defined in Ide.Types

ToJSON PluginId # 
Instance details

Defined in Ide.Types

IsString PluginId # 
Instance details

Defined in Ide.Types

Read PluginId # 
Instance details

Defined in Ide.Types

Methods

readsPrec :: Int -> ReadS PluginId #

readList :: ReadS [PluginId] #

readPrec :: ReadPrec PluginId #

readListPrec :: ReadPrec [PluginId] #

Show PluginId # 
Instance details

Defined in Ide.Types

Methods

showsPrec :: Int -> PluginId -> ShowS #

show :: PluginId -> String #

showList :: [PluginId] -> ShowS #

Eq PluginId # 
Instance details

Defined in Ide.Types

Methods

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

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

Ord PluginId # 
Instance details

Defined in Ide.Types

Methods

compare :: PluginId -> PluginId -> Ordering

(<) :: PluginId -> PluginId -> Bool

(<=) :: PluginId -> PluginId -> Bool

(>) :: PluginId -> PluginId -> Bool

(>=) :: PluginId -> PluginId -> Bool

max :: PluginId -> PluginId -> PluginId

min :: PluginId -> PluginId -> PluginId

Hashable PluginId # 
Instance details

Defined in Ide.Types

Methods

hashWithSalt :: Int -> PluginId -> Int #

hash :: PluginId -> Int #

newtype PluginHandler a (m :: Method ClientToServer Request) #

Combine handlers for the

Constructors

PluginHandler (PluginId -> a -> MessageParams m -> LspM Config (NonEmpty (Either PluginError (MessageResult m)))) 

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

Make a handler for plugins. For how resolve works with this see Note [Resolve in PluginHandlers]

newtype PluginHandlers a #

Instances

Instances details
Monoid (PluginHandlers a) # 
Instance details

Defined in Ide.Types

Semigroup (PluginHandlers a) # 
Instance details

Defined in Ide.Types

class HasTracing (MessageParams m) => PluginMethod (k :: MessageKind) (m :: Method ClientToServer k) where #

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 #

Arguments

:: SMethod m

Method type.

-> MessageParams m

Whether a plugin is enabled might depend on the message parameters e.g. pluginFileType specifies which file extensions a plugin is allowed to handle

-> 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 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 the 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 describes 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. There are requests with no associated URI that, consequentially, cannot inspect the URI.

A common reason why a plugin might not be allowed to respond although 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

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.

Instances

Instances details
PluginMethod 'Notification 'Method_Initialized # 
Instance details

Defined in Ide.Types

PluginMethod 'Notification 'Method_TextDocumentDidChange # 
Instance details

Defined in Ide.Types

PluginMethod 'Notification 'Method_TextDocumentDidClose # 
Instance details

Defined in Ide.Types

PluginMethod 'Notification 'Method_TextDocumentDidOpen # 
Instance details

Defined in Ide.Types

PluginMethod 'Notification 'Method_TextDocumentDidSave # 
Instance details

Defined in Ide.Types

PluginMethod 'Notification 'Method_WorkspaceDidChangeConfiguration # 
Instance details

Defined in Ide.Types

PluginMethod 'Notification 'Method_WorkspaceDidChangeWatchedFiles # 
Instance details

Defined in Ide.Types

PluginMethod 'Notification 'Method_WorkspaceDidChangeWorkspaceFolders # 
Instance details

Defined in Ide.Types

PluginMethod 'Request 'Method_CallHierarchyIncomingCalls # 
Instance details

Defined in Ide.Types

PluginMethod 'Request 'Method_CallHierarchyOutgoingCalls # 
Instance details

Defined in Ide.Types

PluginMethod 'Request 'Method_CodeActionResolve # 
Instance details

Defined in Ide.Types

PluginMethod 'Request 'Method_CodeLensResolve # 
Instance details

Defined in Ide.Types

PluginMethod 'Request 'Method_CompletionItemResolve # 
Instance details

Defined in Ide.Types

PluginMethod 'Request 'Method_TextDocumentCodeAction # 
Instance details

Defined in Ide.Types

PluginMethod 'Request 'Method_TextDocumentCodeLens # 
Instance details

Defined in Ide.Types

PluginMethod 'Request 'Method_TextDocumentCompletion # 
Instance details

Defined in Ide.Types

PluginMethod 'Request 'Method_TextDocumentDefinition # 
Instance details

Defined in Ide.Types

PluginMethod 'Request 'Method_TextDocumentDocumentHighlight # 
Instance details

Defined in Ide.Types

PluginMethod 'Request 'Method_TextDocumentDocumentSymbol # 
Instance details

Defined in Ide.Types

PluginMethod 'Request 'Method_TextDocumentFoldingRange # 
Instance details

Defined in Ide.Types

PluginMethod 'Request 'Method_TextDocumentFormatting # 
Instance details

Defined in Ide.Types

PluginMethod 'Request 'Method_TextDocumentHover # 
Instance details

Defined in Ide.Types

PluginMethod 'Request 'Method_TextDocumentPrepareCallHierarchy # 
Instance details

Defined in Ide.Types

PluginMethod 'Request 'Method_TextDocumentRangeFormatting # 
Instance details

Defined in Ide.Types

PluginMethod 'Request 'Method_TextDocumentReferences # 
Instance details

Defined in Ide.Types

PluginMethod 'Request 'Method_TextDocumentRename # 
Instance details

Defined in Ide.Types

PluginMethod 'Request 'Method_TextDocumentSelectionRange # 
Instance details

Defined in Ide.Types

PluginMethod 'Request 'Method_TextDocumentTypeDefinition # 
Instance details

Defined in Ide.Types

PluginMethod 'Request 'Method_WorkspaceExecuteCommand # 
Instance details

Defined in Ide.Types

PluginMethod 'Request 'Method_WorkspaceSymbol # 
Instance details

Defined in Ide.Types

PluginMethod 'Request ('Method_CustomMethod m :: Method 'ClientToServer 'Request) # 
Instance details

Defined in Ide.Types

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

Make a handler for plugins with no extra data

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

Minimal complete definition

Nothing

Methods

combineResponses #

Arguments

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

Instances details
PluginRequestMethod 'Method_CallHierarchyIncomingCalls # 
Instance details

Defined in Ide.Types

PluginRequestMethod 'Method_CallHierarchyOutgoingCalls # 
Instance details

Defined in Ide.Types

PluginRequestMethod 'Method_CodeActionResolve # 
Instance details

Defined in Ide.Types

PluginRequestMethod 'Method_CodeLensResolve # 
Instance details

Defined in Ide.Types

PluginRequestMethod 'Method_CompletionItemResolve # 
Instance details

Defined in Ide.Types

PluginRequestMethod 'Method_TextDocumentCodeAction # 
Instance details

Defined in Ide.Types

PluginRequestMethod 'Method_TextDocumentCodeLens # 
Instance details

Defined in Ide.Types

PluginRequestMethod 'Method_TextDocumentCompletion # 
Instance details

Defined in Ide.Types

PluginRequestMethod 'Method_TextDocumentDefinition # 
Instance details

Defined in Ide.Types

PluginRequestMethod 'Method_TextDocumentDocumentHighlight # 
Instance details

Defined in Ide.Types

PluginRequestMethod 'Method_TextDocumentDocumentSymbol # 
Instance details

Defined in Ide.Types

PluginRequestMethod 'Method_TextDocumentFoldingRange # 
Instance details

Defined in Ide.Types

PluginRequestMethod 'Method_TextDocumentFormatting # 
Instance details

Defined in Ide.Types

PluginRequestMethod 'Method_TextDocumentHover # 
Instance details

Defined in Ide.Types

PluginRequestMethod 'Method_TextDocumentPrepareCallHierarchy # 
Instance details

Defined in Ide.Types

PluginRequestMethod 'Method_TextDocumentRangeFormatting # 
Instance details

Defined in Ide.Types

PluginRequestMethod 'Method_TextDocumentReferences # 
Instance details

Defined in Ide.Types

PluginRequestMethod 'Method_TextDocumentRename # 
Instance details

Defined in Ide.Types

PluginRequestMethod 'Method_TextDocumentSelectionRange # 
Instance details

Defined in Ide.Types

PluginRequestMethod 'Method_TextDocumentTypeDefinition # 
Instance details

Defined in Ide.Types

PluginRequestMethod 'Method_WorkspaceSymbol # 
Instance details

Defined in Ide.Types

PluginRequestMethod ('Method_CustomMethod m :: Method 'ClientToServer 'Request) # 
Instance details

Defined in Ide.Types

getProcessID :: IO Int #

getPid :: IO Text #

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 () #

type ResolveFunction ideState a (m :: Method ClientToServer Request) = ideState -> PluginId -> MessageParams m -> Uri -> a -> ExceptT PluginError (LspM 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 #

Make a handler for resolve methods. In here we take your provided ResolveFunction and turn it into a PluginHandlers. See Note [Resolve in PluginHandlers]