lsp-1.1.1.0: Haskell library for the Microsoft Language Server Protocol
Safe HaskellNone
LanguageHaskell2010

Language.LSP.Server

Synopsis

Running

runServer Source #

Arguments

:: ServerDefinition config

function to be called once initialize has been received from the client. Further message processing will start only after this returns.

-> IO Int 

Convenience function for 'runServerWithHandles stdin stdout'.

runServerWith Source #

Arguments

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

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

  • onConfigurationChange :: Value -> m (Either Text config)

    onConfigurationChange newConfig is called whenever the clients sends a message with a changed client configuration. This callback should return either the parsed configuration data or an error indicating what went wrong. The parsed configuration object will be stored internally and can be accessed via config.

  • doInitialize :: LanguageContextEnv config -> Message 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 necesary for the server lifecycle. It can also return an error in the initialization if necessary.

  • staticHandlers :: 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 regsitered statically in the initialize request.

  • 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 ()
]

Instances

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

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 #

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) = RequestMessage m -> (Either ResponseError (ResponseResult m) -> f ()) -> f () 
Handler f (m :: Method _from Notification) = NotificationMessage m -> f () 

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

newtype ClientMessageHandler f (t :: MethodType) (m :: Method FromClient t) Source #

Wrapper to restrict Handlers to FromClient 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 #

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 #

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 #

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 #

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 #

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

Defined in Language.LSP.Server.Core

Methods

liftIO :: IO a -> 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 #

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

getConfig :: MonadLsp config m => m (Maybe config) Source #

The current configuration from the client as set via the initialize and workspace/didChangeConfiguration requests.

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

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

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

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

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 => NormalizedUri -> m (Maybe FilePath) Source #

Dump the current text for a given VFS file to a temporary file, 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.

Diagnostics

publishDiagnostics :: MonadLsp config m => Int -> NormalizedUri -> TextDocumentVersion -> 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 DiagnosticSource 
-> m () 

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

Progress

withProgress :: MonadLsp c m => Text -> ProgressCancellable -> ((ProgressAmount -> m ()) -> m a) -> m a Source #

Wrapper for reporting progress to the client during a long running task. withProgress title cancellable f starts a new progress reporting session, and finishes it once f is completed. f is provided with an update function that allows it to report on the progress during the session. If cancellable is Cancellable, f will be thrown a ProgressCancelledException if the user cancels the action in progress.

withIndefiniteProgress :: MonadLsp c m => Text -> ProgressCancellable -> m a -> m a Source #

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

Since: 0.10.0.0

data ProgressAmount Source #

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

Since: 0.10.0.0

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 FromClient t) config. MonadLsp config f => 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.

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.