lsp-2.4.0.0: Haskell library for the Microsoft Language Server Protocol
Safe HaskellSafe-Inferred
LanguageGHC2021

Language.LSP.Server

Synopsis

Running

runServer :: forall config. ServerDefinition config -> IO Int Source #

Convenience function for runServerWithHandles which: (1) reads from stdin; (2) writes to stdout; and (3) logs to stderr and to the client, with some basic filtering.

runServerWith Source #

Arguments

:: LogAction IO (WithSeverity LspServerLog)

The logger to use outside the main body of the server where we can't assume the ability to send messages.

-> LogAction (LspM config) (WithSeverity LspServerLog)

The logger to use once the server has started and can successfully send messages.

-> IO ByteString

Client input.

-> (ByteString -> IO ())

Function to provide output to.

-> ServerDefinition config 
-> IO Int 

Starts listening and sending requests and responses using the specified I/O.

runServerWithHandles Source #

Arguments

:: LogAction IO (WithSeverity LspServerLog)

The logger to use outside the main body of the server where we can't assume the ability to send messages.

-> LogAction (LspM config) (WithSeverity LspServerLog)

The logger to use once the server has started and can successfully send messages.

-> Handle

Handle to read client input from.

-> Handle

Handle to write output to.

-> ServerDefinition config 
-> IO Int 

Starts a language server over the specified handles. This function will return once the exit notification is received.

data VFSData Source #

Constructors

VFSData 

data ServerDefinition config Source #

Contains all the callbacks to use for initialized the language server. it is parameterized over a config type variable representing the type for the specific configuration data the language server needs to use.

Constructors

forall m a. ServerDefinition 

Fields

  • defaultConfig :: config

    The default value we initialize the config variable to.

  • configSection :: Text

    The "config section" that this server uses. This is used to identify the settings that are relevant to the server.

  • parseConfig :: config -> Value -> Either Text config

    parseConfig oldConfig newConfigObject is called whenever we get updated configuration from the client.

    parseConfig is called on the object corresponding to the server's config section, it should not itself try to look for the config section.

    Note that the Value may represent only a partial object in the case where we are handling a workspace/didChangeConfiguration request where the client sends only the changed settings. This is also the main circumstance where the old configuration argument is useful. It is generally fine for servers to ignore this case and just assume that the Value represents a full new config and ignore the old configuration. This will only be problematic in the case of clients which behave as above and *also* don't support workspace/configuration, which is discouraged.

  • onConfigChange :: config -> m ()

    This callback is called any time the configuration is updated, with the new config. Servers that want to react to config changes should provide a callback here, it is not sufficient to just add e.g. a workspace/didChangeConfiguration handler.

  • doInitialize :: LanguageContextEnv config -> TMessage Method_Initialize -> IO (Either ResponseError a)

    Called *after* receiving the initialize request and *before* returning the response. This callback will be invoked to offer the language server implementation the chance to create any processes or start new threads that may be necessary for the server lifecycle. It can also return an error in the initialization if necessary.

  • staticHandlers :: ClientCapabilities -> Handlers m

    Handlers for any methods you want to statically support. The handlers here cannot be unregistered during the server's lifetime and will be registered statically in the initialize request. The handlers provided can depend on the client capabilities, which are static across the lifetime of the server.

  • interpretHandler :: a -> m <~> IO

    How to run the handlers in your own monad of choice, m. It is passed the result of doInitialize, so typically you will want to thread along the LanguageContextEnv as well as any other state you need to run your monad. m should most likely be built on top of LspT.

     ServerDefinition { ...
     , doInitialize = env _req -> pure $ Right env
     , interpretHandler = env -> Iso
        (runLspT env) -- how to convert from IO ~> m
        liftIO        -- how to convert from m ~> IO
     }
    
  • options :: Options

    Configurable options for the server's capabilities.

Handlers

data Handlers m Source #

A mapping from methods to the static Handlers that should be used to handle responses when they come in from the client. To build up a Handlers, you should mconcat a list of notificationHandler and requestHandlers:

mconcat [
  notificationHandler SInitialized $ notif -> pure ()
, requestHandler STextDocumentHover $ req responder -> pure ()
]

Constructors

Handlers 

Fields

Instances

Instances details
Monoid (Handlers config) Source # 
Instance details

Defined in Language.LSP.Server.Core

Methods

mempty :: Handlers config #

mappend :: Handlers config -> Handlers config -> Handlers config #

mconcat :: [Handlers config] -> Handlers config #

Semigroup (Handlers config) Source # 
Instance details

Defined in Language.LSP.Server.Core

Methods

(<>) :: Handlers config -> Handlers config -> Handlers config #

sconcat :: NonEmpty (Handlers config) -> Handlers config #

stimes :: Integral b => b -> Handlers config -> Handlers config #

type family Handler (f :: Type -> Type) (m :: Method from t) = (result :: Type) | result -> f t m where ... Source #

The type of a handler that handles requests and notifications coming in from the server or client

Equations

Handler f (m :: Method _from Request) = TRequestMessage m -> (Either ResponseError (MessageResult m) -> f ()) -> f () 
Handler f (m :: Method _from Notification) = TNotificationMessage m -> f () 

mapHandlers :: (forall (a :: Method ClientToServer Request). Handler m a -> Handler n a) -> (forall (a :: Method ClientToServer Notification). Handler m a -> Handler n a) -> Handlers m -> Handlers n Source #

notificationHandler :: forall (m :: Method ClientToServer Notification) f. SMethod m -> Handler f m -> Handlers f Source #

requestHandler :: forall (m :: Method ClientToServer Request) f. SMethod m -> Handler f m -> Handlers f Source #

newtype ClientMessageHandler f (t :: MessageKind) (m :: Method ClientToServer t) Source #

Wrapper to restrict Handlers to ClientToServer' Methods

Constructors

ClientMessageHandler (Handler f m) 

data Options Source #

Language Server Protocol options that the server may configure. If you set handlers for some requests, you may need to set some of these options.

Constructors

Options 

Fields

Instances

Instances details
Default Options Source # 
Instance details

Defined in Language.LSP.Server.Core

Methods

def :: Options #

LspT and LspM

newtype LspT config m a Source #

Constructors

LspT 

Fields

Instances

Instances details
MonadUnliftIO m => MonadLsp config (LspT config m) Source # 
Instance details

Defined in Language.LSP.Server.Core

Methods

getLspEnv :: LspT config m (LanguageContextEnv config) Source #

MonadTrans (LspT config) Source # 
Instance details

Defined in Language.LSP.Server.Core

Methods

lift :: Monad m => m a -> LspT config m a #

MonadFix m => MonadFix (LspT config m) Source # 
Instance details

Defined in Language.LSP.Server.Core

Methods

mfix :: (a -> LspT config m a) -> LspT config m a #

MonadIO m => MonadIO (LspT config m) Source # 
Instance details

Defined in Language.LSP.Server.Core

Methods

liftIO :: IO a -> LspT config m a #

Applicative m => Applicative (LspT config m) Source # 
Instance details

Defined in Language.LSP.Server.Core

Methods

pure :: a -> LspT config m a #

(<*>) :: LspT config m (a -> b) -> LspT config m a -> LspT config m b #

liftA2 :: (a -> b -> c) -> LspT config m a -> LspT config m b -> LspT config m c #

(*>) :: LspT config m a -> LspT config m b -> LspT config m b #

(<*) :: LspT config m a -> LspT config m b -> LspT config m a #

Functor m => Functor (LspT config m) Source # 
Instance details

Defined in Language.LSP.Server.Core

Methods

fmap :: (a -> b) -> LspT config m a -> LspT config m b #

(<$) :: a -> LspT config m b -> LspT config m a #

Monad m => Monad (LspT config m) Source # 
Instance details

Defined in Language.LSP.Server.Core

Methods

(>>=) :: LspT config m a -> (a -> LspT config m b) -> LspT config m b #

(>>) :: LspT config m a -> LspT config m b -> LspT config m b #

return :: a -> LspT config m a #

MonadCatch m => MonadCatch (LspT config m) Source # 
Instance details

Defined in Language.LSP.Server.Core

Methods

catch :: (HasCallStack, Exception e) => LspT config m a -> (e -> LspT config m a) -> LspT config m a #

MonadMask m => MonadMask (LspT config m) Source # 
Instance details

Defined in Language.LSP.Server.Core

Methods

mask :: HasCallStack => ((forall a. LspT config m a -> LspT config m a) -> LspT config m b) -> LspT config m b #

uninterruptibleMask :: HasCallStack => ((forall a. LspT config m a -> LspT config m a) -> LspT config m b) -> LspT config m b #

generalBracket :: HasCallStack => LspT config m a -> (a -> ExitCase b -> LspT config m c) -> (a -> LspT config m b) -> LspT config m (b, c) #

MonadThrow m => MonadThrow (LspT config m) Source # 
Instance details

Defined in Language.LSP.Server.Core

Methods

throwM :: (HasCallStack, Exception e) => e -> LspT config m a #

MonadUnliftIO m => MonadUnliftIO (LspT config m) Source # 
Instance details

Defined in Language.LSP.Server.Core

Methods

withRunInIO :: ((forall a. LspT config m a -> IO a) -> IO b) -> LspT config m b #

(Applicative m, Monoid a) => Monoid (LspT config m a) Source # 
Instance details

Defined in Language.LSP.Server.Core

Methods

mempty :: LspT config m a #

mappend :: LspT config m a -> LspT config m a -> LspT config m a #

mconcat :: [LspT config m a] -> LspT config m a #

(Applicative m, Semigroup a) => Semigroup (LspT config m a) Source # 
Instance details

Defined in Language.LSP.Server.Core

Methods

(<>) :: LspT config m a -> LspT config m a -> LspT config m a #

sconcat :: NonEmpty (LspT config m a) -> LspT config m a #

stimes :: Integral b => b -> LspT config m a -> LspT config m a #

type LspM config = LspT config IO Source #

class MonadUnliftIO m => MonadLsp config m | m -> config where Source #

Methods

getLspEnv :: m (LanguageContextEnv config) Source #

Instances

Instances details
MonadLsp c m => MonadLsp c (IdentityT m) Source # 
Instance details

Defined in Language.LSP.Server.Core

MonadLsp c m => MonadLsp c (ReaderT r m) Source # 
Instance details

Defined in Language.LSP.Server.Core

MonadUnliftIO m => MonadLsp config (LspT config m) Source # 
Instance details

Defined in Language.LSP.Server.Core

Methods

getLspEnv :: LspT config m (LanguageContextEnv config) Source #

runLspT :: LanguageContextEnv config -> LspT config m a -> m a Source #

data LanguageContextEnv config Source #

Constructors

LanguageContextEnv 

Fields

data m <~> n Source #

How to convert two isomorphic data structures between each other.

Constructors

Iso 

Fields

getClientCapabilities :: MonadLsp config m => m ClientCapabilities Source #

getConfig :: MonadLsp config m => m config Source #

The current configuration from the client as set via the initialize and workspace/didChangeConfiguration requests, as well as by calls to setConfig.

setConfig :: MonadLsp config m => config -> m () Source #

getWorkspaceFolders :: MonadLsp config m => m (Maybe [WorkspaceFolder]) Source #

The current workspace folders, if the client supports workspace folders.

sendRequest :: forall (m :: Method ServerToClient Request) f config. MonadLsp config f => SServerMethod m -> MessageParams m -> (Either ResponseError (MessageResult m) -> f ()) -> f (LspId m) Source #

sendNotification :: forall (m :: Method ServerToClient Notification) f config. MonadLsp config f => SServerMethod m -> MessageParams m -> f () Source #

Config

requestConfigUpdate :: m ~ LspM config => LogAction m (WithSeverity LspCoreLog) -> m () Source #

Send a `worksapce/configuration` request to update the server's config.

This is called automatically in response to `workspace/didChangeConfiguration` notifications from the client, so should not normally be called manually.

tryChangeConfig :: m ~ LspM config => LogAction m (WithSeverity LspCoreLog) -> Value -> m () Source #

Given a new config object, try to update our config with it.

VFS

getVirtualFile :: MonadLsp config m => NormalizedUri -> m (Maybe VirtualFile) Source #

Return the VirtualFile associated with a given NormalizedUri, if there is one.

persistVirtualFile :: MonadLsp config m => LogAction m (WithSeverity VfsLog) -> FilePath -> NormalizedUri -> m (Maybe FilePath) Source #

Dump the current text for a given VFS file to a file in the given directory and return the path to the file.

getVersionedTextDoc :: MonadLsp config m => TextDocumentIdentifier -> m VersionedTextDocumentIdentifier Source #

Given a text document identifier, annotate it with the latest version.

reverseFileMap :: MonadLsp config m => m (FilePath -> FilePath) Source #

If the contents of a VFS has been dumped to a temporary file, map the temporary file name back to the original one.

snapshotVirtualFiles :: LanguageContextEnv c -> STM VFS Source #

Take an atomic snapshot of the current state of the virtual file system.

Diagnostics

publishDiagnostics :: MonadLsp config m => Int -> NormalizedUri -> Maybe Int32 -> DiagnosticsBySource -> m () Source #

Aggregate all diagnostics pertaining to a particular version of a document, by source, and sends a textDocument/publishDiagnostics notification with the total (limited by the first parameter) whenever it is updated.

flushDiagnosticsBySource Source #

Arguments

:: MonadLsp config m 
=> Int

Max number of diagnostics to send

-> Maybe Text 
-> m () 

Remove all diagnostics from a particular source, and send the updates to the client.

Progress

withProgress Source #

Arguments

:: MonadLsp c m 
=> Text

The title of the progress operation

-> Maybe ProgressToken

The progress token provided by the client in the method params, if any

-> ProgressCancellable

Whether or not this operation is cancellable. If true, the user will be shown a button to allow cancellation. Note that requests can still be cancelled even if this is not set.

-> ((ProgressAmount -> m ()) -> m a)

An update function to pass progress updates to

-> m a 

Wrapper for reporting progress to the client during a long running task.

withIndefiniteProgress Source #

Arguments

:: MonadLsp c m 
=> Text

The title of the progress operation

-> Maybe ProgressToken

The progress token provided by the client in the method params, if any

-> ProgressCancellable

Whether or not this operation is cancellable. If true, the user will be shown a button to allow cancellation. Note that requests can still be cancelled even if this is not set.

-> ((Text -> m ()) -> m a)

An update function to pass progress updates to

-> m a 

Same as withProgress, but for processes that do not report the precentage complete.

data ProgressAmount Source #

A package indicating the percentage of progress complete and a an optional message to go with it during a withProgress

Since: 0.10.0.0

Constructors

ProgressAmount (Maybe UInt) (Maybe Text) 

data ProgressCancellable Source #

Whether or not the user should be able to cancel a withProgress/withIndefiniteProgress session

Since: 0.11.0.0

Dynamic registration

registerCapability :: forall f t (m :: Method ClientToServer t) config. MonadLsp config f => LogAction f (WithSeverity LspCoreLog) -> SClientMethod m -> RegistrationOptions m -> Handler f m -> f (Maybe (RegistrationToken m)) Source #

Sends a client/registerCapability request and dynamically registers a Method with a Handler. Returns Nothing if the client does not support dynamic registration for the specified method, otherwise a RegistrationToken which can be used to unregister it later.

unregisterCapability :: MonadLsp config f => RegistrationToken m -> f () Source #

Sends a client/unregisterCapability request and removes the handler for that associated registration.

data RegistrationToken (m :: Method ClientToServer t) Source #

reverseSortEdit :: WorkspaceEdit -> WorkspaceEdit Source #

The changes in a workspace edit should be applied from the end of the file toward the start. Sort them into this order.