Skip to content

ssmucny/FsharpLspExample

Folders and files

NameName
Last commit message
Last commit date

Latest commit

 

History

1 Commit
 
 
 
 
 
 
 
 
 
 
 
 

Repository files navigation

Language Server Protocol in F#

Creating a new programming language has never been without its struggles, but historically, one of the biggest hurdles to overcome was building a quality editor experience. Furthermore, things like syntax highlighting, information on hover, and the all important red squiggle are now table stakes for any language whether it be simple text markup or a radical exploration into typed algebraic effects.

The Language Server Protocol (LSP) was introduced in 2016 as an attempt to standardize what it means to have 'editor tooling'; by and large it has been wildly successful. It turns an N x N problem into an N + N problem that benefits both language implementers and programmers alike. Implementors only need to target a single API and programmers can use their favorite editor!

I've spent the better part of the past year designing and implementing my own programming language (ProtoGraph) and one of the most important features has been a good LSP implementation. While there are several existing projects that implement a server in F# using LanguageServerProtocol (including the main F# LSP implementation, FsAutoComplete), there is a dearth of quality tutorials on how to write your own server, specifically in F#, so I thought it would be a good idea to share some of what I found along the way.

In this article I'll be using an exceedingly simple and arbitrary file format to show how to set up a simple LSP server. You can then use this example as a template if you want to kickstart your own language server.

Screenshot_20251202_001116.png

If you want to follow along, the full source code for the example in this article can be found at https://git.samsmucny.com/ssmucny/FsharpLspExample. To build and run the example, you'll need to have the .NET 10 SDK installed along with Node.js and Visual Studio Code.

Quickstart steps to run this repository:

  1. Run dotnet build with .NET 10 SDK
  2. Edit the paths in the Client/src/extension.js file to point to the built server DLL and the dotnet CLI (probably in LspExample/bin/Debug/net10.0)
  3. Open the Client folder in VSCode
  4. Run npm install to install the VSCode extension dependencies
  5. Launch the VSCode debugger for the extension
  6. Open a file with the *.demo extension

Contents


To get started, you're going to need a new F# dotnet project and add the LanguageServerProtocol as a dependency. If you need help setting up a new F# project, see the official documentation for getting started with F#.

Note

Many of the F# types in the LanguageServerProtocol source code were automatically generated from the LSP specification. Check out the Amplifying F# stream to see how it was done! Fabulously Generating the Language Server Protocol in F#

LanguageServerProtocol Library

Once you have a project set up we'll need two new types to underpin our server: Server and Client. They will inherit from base classes in the LSP library, and these classes will be the primary way we communicate with the LSP client (in this case VSCode), and we will do this by overriding methods defined on the base classes.

LspExample/Server.fs

/// <summary>
/// The Server is the stateful object that handles LSP requests from the client process.
/// The individual capabilities are defined on the LspServer base class and overridden with real behavior if supported.
/// </summary>
/// <see href="https://microsoft.github.io/language-server-protocol/specifications/lsp/3.17/specification/#lifeCycleMessages"/>
type Server(client: Client) =
    inherit LspServer()

And then we add the Client:

LspExample/Client.fs

/// <summary>
/// The Client is not the client process (the IDE host);
/// it is an object that can communicate with the host client by sending it messages.
/// This is in contrast to the Server which can only receive messages from the host client.
/// </summary>
type Client(notificationSender: Server.ClientNotificationSender, requestSender: Server.ClientRequestSender) =
    inherit LspClient()

    member this.ShowInfo(message) =
        this.WindowShowMessage(
            { Type = Types.MessageType.Info
              Message = message }
        )

    member this.ShowError(message) =
        this.WindowShowMessage(
            { Type = Types.MessageType.Error
              Message = message }
        )

    member this.LogDebug(message) =
        this.WindowLogMessage(
            { Type = Types.MessageType.Debug
              Message = message }
        )

    override this.WindowLogMessage p =
        match box p with
        | null -> async { }
        | value -> notificationSender "window/logMessage" value |> Async.Ignore

    override this.WindowShowMessage p =
        match box p with
        | null -> async { }
        | value -> notificationSender "window/showMessage" value |> Async.Ignore

    override this.WindowShowMessageRequest p =
        match box p with
        | null ->
            async { return Result.Error(Error.InternalError("Attempted to send message, but the parameter was null")) }
        | value -> requestSender.Send "window/showMessageRequest" value

The client is not actually the client like VSCode, but it represents our method of sending various messages to the client. Here, we're just overriding the methods for sending notification messages to the client, and adding some helper methods to go along with them.

Warning

Do NOT read/write to/from standard input/output within your server process. The LSP protocol takes over stdio for communication between the client and server, and if the server process interferes with that then the entire process will be terminated. Always use the Client methods to send messages to the client process and use a separate logger sink if you need to persist logs somewhere else.

Server Initialization

Before we can start the server, there is some more setup that is needed to handle the lifecycle functions of the LSP.

The first couple of functions are just helpers that we will be using in the rest of the server, but pay attention to the fileContents since that is where we will be storing the state of files that are opened by the client. You'll also notice the capabilities which is what we will use to tell the client what features we support (and will override in the Server class).

LspExample/Server.fs

/// Helper methods to catch errors to prevent the server from crashing
let handleAnyError (exn: Exception) (memberName: string) =
    async {
        do!
            client.ShowError(
                $"Internal error in %s{memberName}:\n%s{exn.Message}\n%s{exn.StackTrace}\nSource:\n%s{exn.Source}"
            )

        return Result.Error(Error.InternalError $"{memberName} failed due to an internal error")
    }

/// Store of synced files from the client mapping the file Uri to the contents
let fileContents = ConcurrentDictionary<string, FileContent>()

/// Get the contents of a document from the cache if present. If not present then read it from disk.
let documentContents documentUri =
    match fileContents.TryGetValue documentUri with
    | Success(FileContent(_, contents)) -> contents
    | Nothing -> uriToPath documentUri |> AbsolutePath.toString |> File.ReadAllText

/// The supported capabilities of this server. These are communicated to the client process on startup.
let capabilities: ServerCapabilities =
    { ServerCapabilities.Default with
        TextDocumentSync = Some(U2.C2 TextDocumentSyncKind.Full)
        HoverProvider = Some(U2.C1 true)
        DiagnosticProvider =
            Some(
                U2.C1
                    { InterFileDependencies = false
                      Identifier = Some "DemoLang"
                      WorkspaceDiagnostics = false
                      WorkDoneProgress = None }
            )
        SemanticTokensProvider =
            Some(
                U2.C1
                    { WorkDoneProgress = None
                      Legend =
                        { TokenTypes = SemanticTokens.tokenTypes
                          TokenModifiers = SemanticTokens.tokenModifiers }
                      Range = Some(U2.C1 true)
                      Full = Some(U2.C1 true) }
            ) }

The actual lifecycle methods handle the initialization and the open/edit/close of documents. The purpose of the methods should be clear from their names: Initialize/Initialized run on startup, and Open/Close/Change update the fileContents cache with data from the client.

LspExample/Server.fs

/// This is only run once on startup and is treated like a constructor.
/// Certain things can be initialized here safely before they are used in other methods.
override this.Initialize param =
    async {
        do!
            client.WindowShowMessage(
                { Type = MessageType.Info
                  Message = "Initializing the language server" }
            )

        return
            Result.Ok
                { InitializeResult.Capabilities = capabilities
                  ServerInfo =
                    Some
                        { InitializeResultServerInfo.Name = "Demo Language Server"
                          Version = Some "0.0.1" } }
    }

override this.Initialized param =
    async { do! client.ShowInfo("Initialized") }

override this.TextDocumentDidOpen param =
    async {
        try
            let textDoc = param.TextDocument

            if fileContents.TryAdd(textDoc.Uri, FileContent(textDoc.Version, textDoc.Text)) then
                do! client.ShowInfo($"Opened {textDoc.Uri}")
            else
                failwith "File already opened"
        with exn ->
            return! handleAnyError exn (nameof this.TextDocumentDidOpen) |> Async.Ignore
    }

override this.TextDocumentDidClose param =
    async {
        try
            let textDoc = param.TextDocument

            if fileContents.Remove(textDoc.Uri) |> fst then
                do! client.ShowInfo($"Closed {textDoc.Uri}")
            else
                failwith "Cannot close file that is not opened"
        with exn ->
            return! handleAnyError exn (nameof this.TextDocumentDidClose) |> Async.Ignore
    }

override this.TextDocumentDidChange param =
    async {
        try
            let textDoc = param.TextDocument
            let changes = param.ContentChanges

            if changes.Length <> 1 then
                failwith "Multiple changes not supported by server"

            let wholeDocumentChange = changes[0]

            match wholeDocumentChange with
            | U2.C1 _ -> failwith "Partial document changes not supported by server"
            | U2.C2 { Text = newText } ->
                let newDocument = FileContent(textDoc.Version, newText)
                let updateDocument =
                    Func<_, _, _>(fun uri (FileContent(oldVersion, _) as old) ->
                        if textDoc.Version > oldVersion then newDocument else old)

                fileContents.AddOrUpdate(textDoc.Uri, newDocument, updateDocument) |> ignore
                do! client.LogDebug($"Updated {textDoc.Uri}")

        with exn ->
            return! handleAnyError exn (nameof this.TextDocumentDidChange) |> Async.Ignore
    }

There are a couple things to point out above that will apply to the other capabilities later on in the article: async and exception handling.

All the methods in the Client and Server return some type of async result (some are an Async and Result return type combined). This allows the server to stay responsive to multiple requests at once, but because of this you will need to carefully manage mutable state (like with fileContents). For the async methods, you should also try to wrap the entire method body in the async computation expression. This way the entire method can be invoked asynchronously. If you push down the async expressions, then the methods will be invoked mostly synchronously and will only yield control when the async value is returned. This is similar using Task-returning functions which are 'hot' in contrast to Async functions which are 'cold'.

All the methods after the Initialize include a try/with expression to catch any exceptions. This is a core promise of the server: you CANNOT crash. No matter what error you encounter, continuing with some level of service in any capacity will almost certainly be better than stopping all together. Clients will usually attempt to restart the server after a crash, but this is not something you should rely upon since all your state will be wiped.

The last part we need to get the language server up and running is the main file. The first half is mostly boilerplate to manage the JSON RPC protocol; the part we care about is near the bottom.

LspExample/LSP.fs

/// The entry point for the language server program.
/// The first couple definitions are mostly boilerplate and just help with converting to/from JsonRpc
/// which is the protocol used by the LSP.
module LspExample.LSP

open System
open System.Threading.Tasks
open Ionide.LanguageServerProtocol
open Ionide.LanguageServerProtocol.JsonUtils
open LspExample
open Newtonsoft.Json
open StreamJsonRpc

let private defaultJsonRpcFormatter () =
    let jsonRpcFormatter = new JsonMessageFormatter()
    jsonRpcFormatter.JsonSerializer.NullValueHandling <- NullValueHandling.Ignore
    jsonRpcFormatter.JsonSerializer.ConstructorHandling <- ConstructorHandling.AllowNonPublicDefaultConstructor
    jsonRpcFormatter.JsonSerializer.MissingMemberHandling <- MissingMemberHandling.Ignore
    jsonRpcFormatter.JsonSerializer.Converters.Add(StrictNumberConverter())
    jsonRpcFormatter.JsonSerializer.Converters.Add(StrictStringConverter())
    jsonRpcFormatter.JsonSerializer.Converters.Add(StrictBoolConverter())
    jsonRpcFormatter.JsonSerializer.Converters.Add(SingleCaseUnionConverter())
    jsonRpcFormatter.JsonSerializer.Converters.Add(OptionConverter())
    jsonRpcFormatter.JsonSerializer.Converters.Add(ErasedUnionConverter())
    jsonRpcFormatter.JsonSerializer.ContractResolver <- OptionAndCamelCasePropertyNamesContractResolver()
    jsonRpcFormatter

let private jsonRpcFormatter = defaultJsonRpcFormatter ()

let private createRpc (handler: IJsonRpcMessageHandler) : JsonRpc =
    let rec (|HandleableException|_|) (e: exn) =
        match e with
        | :? LocalRpcException -> Some()
        | :? TaskCanceledException -> Some()
        | :? OperationCanceledException -> Some()
        | :? Newtonsoft.Json.JsonSerializationException -> Some()
        | :? System.AggregateException as aex ->
            aex.InnerExceptions |> Seq.tryHead |> Option.bind (|HandleableException|_|)
        | _ -> None

    let (|Flatten|_|) (e: exn) =
        match e with
        | :? AggregateException as aex ->
            let aex = aex.Flatten()
            aex.InnerExceptions |> Seq.tryHead |> Option.defaultValue e |> Some
        | _ -> Some e

    let strategy = StreamJsonRpc.ActivityTracingStrategy()

    { new JsonRpc(handler, ActivityTracingStrategy = strategy) with
        member this.IsFatalException(ex: Exception) =
            match ex with
            | HandleableException -> false
            | _ -> true

        member this.CreateErrorDetails(request: Protocol.JsonRpcRequest, ex: Exception) =
            let isSerializable = this.ExceptionStrategy = ExceptionProcessing.ISerializable

            match ex with
            | Flatten(:? Newtonsoft.Json.JsonSerializationException as ex) ->

                let data: obj = if isSerializable then ex else Protocol.CommonErrorData(ex)

                Protocol.JsonRpcError.ErrorDetail(
                    Code = Protocol.JsonRpcErrorCode.ParseError,
                    Message = ex.Message,
                    Data = data
                )
            | _ -> base.CreateErrorDetails(request, ex) }

/// Start the LSP server
let private startCore () =

    // The LSP protocol takes over stdio. DO NOT read from or write to stdio under ANY circumstances.
    // The process will terminate if you do. To send messages to the user, use the Client type.
    let input = Console.OpenStandardInput()
    let output = Console.OpenStandardOutput()

    /// Create the handlers that we can work with. Custom extensions can be added here if desired.
    /// See the F# Ionide language server (FsAutoComplete) for examples on how to add custom request types
    /// https://github.com/ionide/FsAutoComplete/blob/9b8de8c575faaa6016ffe69236686d83fe7e0e56/src/FsAutoComplete/LspServers/AdaptiveFSharpLspServer.fs#L3206
    let requestHandlings: Map<string, Mappings.ServerRequestHandling<_>> =
        Ionide.LanguageServerProtocol.Server.defaultRequestHandlings ()

    use jsonRpcHandler =
        new HeaderDelimitedMessageHandler(output, input, defaultJsonRpcFormatter ())

    // Start the server process
    // Do some bootstrapping by injecting the dependencies
    Server.start
        requestHandlings
        input
        output
        // Create the client. It is provided notifier and requester which are used to send messages to the actual separate client process.
        (fun (notifier, requester) -> new Client(notifier, requester))
        // The created client will be provided to the server initializer here which is where the LSP logic happens.
        (fun client -> new Server(client))
        createRpc

let private StartLanguageServer () =
    try
        let result = startCore ()
        int result
    with ex ->
        eprintfn $"Language server crashed with: %A{ex}"
        raise ex

[<EntryPoint>]
let main args = StartLanguageServer()

With this we can now run the program and get… nothing. The server will start up and wait for a client to start communicating on standard in which will never happen. To test things, we are going to need to set up a client process.

Setting up the Client

To see our server in action we'll need to set up a client process. Below are the primary files we will need to test our server in VSCode. For our purposes, the client is just a thin shell that we can use to run the server executable. Be aware that you'll need to set the paths to the correct files for the command and arguments yourself in the extension.js file (likely located somewhere in LspExample/bin/Debug/net10.0). In a proper extension these would be automatically discovered or obtained via configuration settings. We also need a language-configuration.json file. VSCode uses this to provide shortcuts and auto-indent and auto-closing pairs, but we will be leaving it mostly empty.

Now we can finally launch the client debugger and see our server initialized when we open a *.demo file.

Screenshot_20251202_002954-1.png


Adding Capabilities

Now that we have a running server, you probably want to add functionality for all those cool LSP features. The nice thing is that adding support for a new capability is pretty simple. You just need to do two things: add the new capability to the capabilities record that is sent to the client during initialization, and override the corresponding method. Check out the LSP specification for a detailed list of all the features. The types and methods in the F# library also conveniently include much of the information directly from the specification as documentation comments.

If you have been following along, you may have noticed that I have omitted several types that were referenced in some of the above code snippets, or also that while the client started the server it also closed it shortly after.

First, I'll drop the domain we'll be working with along with the remaining helper functions.

The first couple of definitions are for a wrapper around strings to add a little extra type safety with conversions to and from the text document URI which is quite temperamental. You have to handle Windows as well as Posix style paths and worse--the URI may or may not be URI encoded!

LspExample/Types.fs

/// <summary>
/// An absolute path on the file system. Should be a real file or directory.
/// </summary>
type AbsolutePath = AbsolutePath of string

/// Functions for working with AbsolutePaths
module AbsolutePath =
    /// Handle windows path separators
    let private deDOS (path: string) =
        if Path.DirectorySeparatorChar = '\\' then
            path.Replace('\\', '/')
        else
            path
            
    let ofUri (uri: Uri) =
        uri.AbsolutePath |> Uri.UnescapeDataString |> deDOS |> AbsolutePath

    let toString (AbsolutePath path) = path

    let toUri (AbsolutePath path) =
        if Environment.OSVersion.Platform = PlatformID.Win32NT then
            $"file:///%s{path}"
        else
            $"file://%s{path}"

/// <summary>
/// Convert a file URI from the client to an absolute file path for the local file system.
/// </summary>
/// <remarks>Removes the schema and unescapes any specially encoded characters because the LSP spec does not specify if characters are encoded.</remarks>
/// <param name="uri">The file URI to convert</param>
let uriToPath (uri: string) =
    uri |> Uri.UnescapeDataString |> Uri |> AbsolutePath.ofUri

The next part includes a couple of helper functions that we will be using, one of which uses active patterns (the funky banana clips (|_|_|)) to make pattern matching feel a little bit cleaner.

LspExample/Types.fs

/// Active pattern to make working with .NET BCL Try* functions nicer 
let (|Success|Nothing|) (valueFound: bool, value: 'a) =
    if valueFound then Success value else Nothing

/// Construct an LSP range record
let range (startLine: int, startColumn: int) (endLine: int, endColumn: int) : Range =
    { Start =
        { Line = uint32 startLine
          Character = uint32 startColumn }
      End =
        { Line = uint32 endLine
          Character = uint32 endColumn } }

And finally, we have the domain of the 'language' we will be parsing. It just consists of multiple lines where each line can either have a number, text, or be empty (white space).

LspExample/Types.fs

/// Define the abstract types of the simple demo language
module DemoLang =

    type Value =
        | Number of float
        | Text of string
        | Empty of string

    type Line =
        { Line: int
          Contents: string
          Value: Value }

The capabilities that the server supports are communicated at startup, and the capabilities we will be implementing here are at LspExample/Server.fs which was shown previously. If you add a capability, you need to override the corresponding method on the Server class.

Diagnostics

The diagnostic capability can be added by overriding the TextDocumentDiagnostic capability. This will parse the document contents (which may or may not be in the cache) and generate various messages to display to the user. In this example we only support full reports, so every time we will reparse and validate the entire document. For larger files and more complex programming languages, you will probably want to use incremental updates with more intelligent caching of results to reduce the amount of redundant work done on every keystroke.

Here, we are also providing support for pull diagnostics which is a newer LSP capability where the client can request when it wants the server to generate diagnostics which provides more control to the client compared to the older push model. If you want to support older clients or the ability to process diagnostics in the background, you should use TextDocumentPublishDiagnostics instead which is a method on the Client that you call instead of a method you override in the Server.

LspExample/Server.fs

override this.TextDocumentDiagnostic param =
    async {
        try
            do! client.LogDebug($"Diagnostics for {param.TextDocument.Uri}")

            let diagnostics =
                param.TextDocument.Uri |> documentContents |> Diagnostics.DocumentDiagnostics

            do! client.LogDebug($"Diagnostic messages:\n%A{diagnostics}")

            let report =
                { Kind = "full"
                  ResultId = None
                  Items = diagnostics
                  RelatedDocuments = None }

            return LspResult.success (U2.C1 report)
        with exn ->
            return! handleAnyError exn (nameof this.TextDocumentDiagnostic)
    }

The function we use to generate diagnostics is simple but demonstrates the primary way you construct messages using the Diagnostic type which are bundled into a full report. The diagnostics we generate here are the following:

  • Warn: if a line is more than 80 characters long
  • Warn: if a line is not empty and consists of only whitespace
  • Error: if a line has leading space
  • Warn: if a line has trailing space
  • Error: if a parsed number is negative

Crafting good error messages in a compiler is an art form, and for complex languages you should try to provide as much relevant information as possible without overloading the user. Elm and Rust are great examples of compilers that do a great job in this department.

LspExample/Diagnostics.fs

let private diagnostic severity range message =
    { Range = range
      Severity = Some severity
      Code = None
      CodeDescription = None
      Source = Some "demolang"
      Message = message
      Tags = None
      RelatedInformation = None
      Data = None }

let private generateDiagnosticsForLine
    { Contents = contents
      Line = line
      Value = value }
    : Diagnostic seq =
    seq {
        if contents.Length > 80 then
            diagnostic
                DiagnosticSeverity.Warning
                (range (line, 0) (line, contents.Length - 1))
                $"Line too long: {contents.Length} columns"

        if String.IsNullOrWhiteSpace contents && contents.Length > 0 then
            diagnostic
                DiagnosticSeverity.Warning
                (range (line, 0) (line, contents.Length))
                "Line is non-empty and contains whitespace"
        else
            let noLeadingSpaces = contents.TrimStart()

            if noLeadingSpaces <> contents then
                diagnostic
                    DiagnosticSeverity.Error
                    (range (line, 0) (line, contents.Length - noLeadingSpaces.Length))
                    "Line has leading whitespace"

            let noTrailingSpaces = contents.TrimEnd()

            if noTrailingSpaces <> contents then
                diagnostic
                    DiagnosticSeverity.Warning
                    (range (line, noTrailingSpaces.Length) (line, contents.Length))
                    "Line has trailing whitespace"

        match value with
        | Number number when number < 0 ->
            diagnostic
                DiagnosticSeverity.Error
                (range (line, 0) (line, contents.Length))
                "Negative numbers are not supported"
        | _ -> ()

    }

/// <summary>
/// Generate diagnostics for file contents: info, warnings, and errors
/// </summary>
/// <param name="contents">The file contents to generate diagnostics for</param>
let DocumentDiagnostics (contents: string) : Diagnostic[] =
    let documentLines = Parser.ParseFile contents

    documentLines |> Seq.collect generateDiagnosticsForLine |> Seq.toArray

You may have wondered how we are parsing our file. Well, here it is:

LspExample/Parser.fs

let private parseLine (line: string) =
    match Double.TryParse(line.AsSpan()) with
    | Success parsedNumber -> Value.Number parsedNumber
    | Nothing when String.IsNullOrWhiteSpace line -> Value.Empty line
    | Nothing -> Value.Text line

/// <summary>
/// Parse an entire file into structured data.
/// </summary>
/// <param name="contents">The entire contents of a file</param>
/// <remarks>For large files and complex languages you should consider caching AST results and using incremental updated
/// instead of reparsing the full file update from the client every time something changes.</remarks>
let ParseFile (contents: string) : Line[] =
    contents.Split('\n')
    |> Array.mapi (fun line contents ->
        { Line = line
          Contents = contents
          Value = parseLine contents })

Pretty simple, right? However, this isn't a tutorial on writing a parser, so if you are interested in learning more I'd recommend looking at a parser combinator library like FParsec or XParsec to get started. The evergreen content on F# for Fun and Profit: Understanding Parser Combinators is also a great guide.

Important

Expect the input to be malformed. Not only should the parser gracefully handle improper inputs and generate specific diagnostics, but it should also be able to recover and continue parsing the rest of the input as best as possible. Many parsing tutorials don't cover this in depth because the error handling and recovery can quickly balloon the complexity of a parser when you are just learning the fundamentals. Your best resource is likely going to be learning how other languages handle partial, malformed, and ambiguous user input.

Now that we have the diagnostic capability, when VSCode opens a demo file it will request the diagnostics and give you those sweet sweet squiggles in your code.

Screenshot_20251203_195336.png

Hover

The next capability we will add is hover which gives you contextual information when you hover your cursor over a position in the file. This is often used for showing types for values and documentation.

LspExample/Server.fs

override this.TextDocumentHover param =
    async {
        try
            do! client.LogDebug($"Hover for {param.TextDocument.Uri} at {param.Position.DebuggerDisplay}")

            let hoverResult =
                param.TextDocument.Uri
                |> documentContents
                |> Parser.ParseFile
                |> Hover.LookupHover param.Position

            return Result.Ok(Some hoverResult)
        with exn ->
            return! handleAnyError exn (nameof this.TextDocumentHover)
    }

LspExample/Hover.fs

/// <summary>
/// The hover capability shows a tooltip when you hover over something of interest.
/// </summary>
/// <see href="https://microsoft.github.io/language-server-protocol/specifications/lsp/3.17/specification/#textDocument_hover"/>
module LspExample.Hover

open Ionide.LanguageServerProtocol.Types
open LspExample.Types
open LspExample.Types.DemoLang

/// <summary>
/// Generate hover information: the type of the value and some information about it
/// </summary>
/// <param name="hoverLocation">Where the hover is requested</param>
/// <param name="contents">The parsed file to lookup within</param>
let LookupHover (hoverLocation: Position) (contents: Line[]) : Hover =
    match contents |> Array.tryItem (int hoverLocation.Line) with
    | Some { Value = Number number
             Contents = contents
             Line = line } ->
        { Contents =
            U3.C1
                { MarkupContent.Kind = MarkupKind.PlainText
                  Value = $"(Number) {number}" }
          Range = range (line, 0) (line, contents.Length) |> Some }
    | Some { Value = Text text
             Contents = contents
             Line = line } ->
        let leading = text.TrimStart()
        let trailing = text.TrimEnd()

        { Contents =
            U3.C1
                { MarkupContent.Kind = MarkupKind.PlainText
                  Value = $"(Text) Length={text.Trim().Length}" }
          Range = range (line, contents.Length - leading.Length) (line, trailing.Length) |> Some }
    | _ ->
        { Contents =
            U3.C1
                { MarkupContent.Kind = MarkupKind.PlainText
                  Value = "No hover information to display here" }
          Range = None }

Like with diagnostics, we are reparsing the entire file each time we try to generate a hover value which is fine for this simple file format but won't scale for larger programs. In this example we provide contextual hover information based on the type of line we are at:

  • For numbers: (Number) <value of the number>
  • For text: (Text) <length of the trimmed text>
  • Nothing for other stuff

Tip

While we didn't use it here, the hover capability in some clients also supports markdown! This can be a great way to add some simple formatting to your hover tool-tips.

Now that we have hover, we can get inspect our code just by moving our mouse over it:

Screenshot_20251203_201543.png

Semantic Tokens

The final thing we will be adding here is semantic tokens. These are generally used to provide syntax highlighting in the editor. While you can use semantic tokens for syntax highlighting, many editors also have a separate method available. In VSCode this is done through regex matches in textmate grammars, but other editors can use more advanced tools like Tree-sitter. Choosing how much you rely on semantic tokens versus the editor specific solution depends on your language and personal preferences:

Semantic Tokens Editor Specific (Regex, Tree-sitter, etc.)
Write once, works on any supported editor Need to add support for each editor's format
Semantic sensitive (mutable, async, etc.) Basic lexical analysis or context-sentitive using token-based AST
Can be slower to update Independent of server and is usually very responsive
If it fails the experience is heavily degraded Provides a fallback/basic syntax highlighting if the server is still loading or unresponsive

Some of the slowness of generating many thousands of tokens can be mitigated by allowing the generation of only a range instead of the whole file, and again, intelligent caching of intermediate stages of the compiler can greatly speed up the recomputation of things like semantic tokens.

Tip

One does not need to choose one or the other. You can use both! One option is to use the editor specific tool to provide basic syntax highlighting for simple (ie. context-free) things like keywords and literals and use semantic tokens for providing richer colors on top. I also find this provides a nice 'pop-in' color effect when a user first opens a file. They first see the basic highlighting which enables them to start reading the code, and then once the semantic tokens are calculated more items get highlighted which signals that the all the file metadata has been computed successfully by the server.

In this example, we will have support for both full and range based updates, but for simplicity, under the hood we will just recalculate everything like we have done before.

LspExample/Server.fs

override this.TextDocumentSemanticTokensRange param =
    async {
        try
            do! client.LogDebug($"Partial semantic tokens requested for {param.Range.DebuggerDisplay}")

            let tokens: uint32[] =
                param.TextDocument.Uri
                |> documentContents
                |> Parser.ParseFile
                |> SemanticTokens.SemanticTokenArray

            do! client.LogDebug($"Finished semantic tokens: Count={tokens.Length}")
            return Result.Ok(Some { Data = tokens; ResultId = None })
        with exn ->
            return! handleAnyError exn (nameof this.TextDocumentSemanticTokensRange)
    }

override this.TextDocumentSemanticTokensFull param =
    async {
        do! client.LogDebug("Full semantic tokens requested")
        return!
            this.TextDocumentSemanticTokensRange
                { WorkDoneToken = param.WorkDoneToken
                  SemanticTokensRangeParams.PartialResultToken = param.PartialResultToken
                  TextDocument = param.TextDocument
                  Range =
                    { Start = { Line = 0u; Character = 0u }
                      End =
                        { Line = UInt32.MaxValue - 1u // adjust for overflow
                          Character = 0u } } }
    }

Because of the large number of tokens that are usually generated, the semantic token API uses a special format to send them over the wire. To help manage this, I have some extra types to help model the small domain of semantic tokens. You can read more about the packed format on the LSP specification site.

LspExample/SemanticTokens.fs

/// <summary>
/// Generation of semantic tokens
/// </summary>
/// <see href="https://microsoft.github.io/language-server-protocol/specifications/lsp/3.17/specification/#textDocument_semanticTokens"/>
module LspExample.SemanticTokens

open System
open LspExample.Types.DemoLang

/// <summary>
/// Unit of measure for semantic token types
/// </summary>
[<Measure>]
type private Type

/// <summary>
/// Semantic tokens used by this server
/// </summary>
/// <remarks>Types should have integral values starting from 0 and increasing</remarks>
[<RequireQualifiedAccess>]
module Type =
    let String = 0u<Type>
    let Number = 1u<Type>

/// <summary>
/// The string names of the semantic token types that are used by this server. Communicated to the client on startup
/// </summary>
/// <remarks>The index of the names must match the numbers assigned in the Type module</remarks>
let tokenTypes = [| "string"; "number" |]

/// <summary>
/// Unit of measure for semantic tokens modifiers
/// </summary>
[<Measure>]
type private Modifier

/// <summary>
/// Semantic token modifiers used by this server
/// </summary>
/// <remarks>Modifiers should have numerical values based on powers of 2 because they are packed into a bit array (uint32)</remarks>
[<RequireQualifiedAccess>]
module Modifier =
    let ReadOnly = 1u<Modifier>

let private packModifiers (modifiers: uint32<Modifier>[]) = Array.sum modifiers

/// <summary>
/// The string names of the semantic token modifiers that are used by this server. Communicated to the client on startup
/// </summary>
/// <remarks>The index of the names must match the numbers assigned in the Modifier module</remarks>
let tokenModifiers = [| "readonly" |]

/// <summary>
/// A token is a range in the source code that has some semantic meaning (function/variable name, or keyword, or type for example).
/// Tokens may overlap, but they must be ordered when sent over the wire because the packed format uses relative positioning.
/// </summary>
[<Struct>]
type private Token =
    { Line: uint32
      StartChar: uint32
      Length: uint32
      TokenType: uint32<Type>
      TokenModifiers: uint32<Modifier> }

    static member create
        (line: int, column: int, length: int, tokenType: uint32<Type>, [<ParamArray>] tokenModifiers: uint32<Modifier>[]) =
        { Line = uint32 line
          StartChar = uint32 column
          Length = uint32 length
          TokenType = tokenType
          TokenModifiers = packModifiers tokenModifiers }

let private packToken (token: Token) =
    [| token.Line
       token.StartChar
       token.Length
       uint32 token.TokenType
       uint32 token.TokenModifiers |]
    
/// <summary>
/// Convert tokens from absolute to relative positioning
/// </summary>
/// <param name="tokens">The tokens to transform</param>
let private makeTokensRelative (tokens: #seq<Token>) : Token seq =

    if Seq.isEmpty tokens then
        Seq.empty
    else
        seq {
            yield Seq.head tokens

            yield!
                tokens
                |> Seq.pairwise
                |> Seq.map (fun (predecessor, current) ->
                    assert (predecessor.Line <= current.Line)
                    assert (predecessor.Line = current.Line || predecessor.StartChar <= current.StartChar)

                    { Token.Line = current.Line - predecessor.Line
                      Length = current.Length
                      TokenModifiers = current.TokenModifiers
                      TokenType = current.TokenType
                      StartChar =
                        if current.Line = predecessor.Line then
                            current.StartChar - predecessor.StartChar
                        else
                            current.StartChar })

The semantic tokens domain centers around two special types: Type and Modifier that use the F# units of measure feature to provide more type-safe methods of constructing tokens. Units of measure are a zero-cost abstraction that allows you to tag types with a dimension that prevents you from accidentally using improper types, and for numerical uses they can be combined using the normal rules of dimensional analysis.

Using the above helper functions, the code to generate our semantic tokens is nice and terse:

LspExample/SemanticTokens.fs

let private packAllTokens (tokens: #seq<Token>) : uint32[] =
    tokens |> makeTokensRelative |> Seq.collect packToken |> Seq.toArray

/// <summary>
/// Generate semantic tokens for a series of lines
/// </summary>
/// <param name="lines">Lines to generate tokens from</param>
let SemanticTokenArray (lines: #seq<Line>) : uint32[]=
    lines
    |> Seq.choose (fun line ->
        match line with
        | { Value = Empty _ } -> None
        | { Value = Number _
            Contents = contents
            Line = line } -> Some <| Token.create (line, 0, contents.Length, Type.Number, Modifier.ReadOnly)
        | { Value = Text text; Line = line } ->
            Some <| Token.create (line, 0, text.Length, Type.String, Modifier.ReadOnly))
    |> packAllTokens

Finally, we have syntax highlighting!

Screenshot_20251203_205441.png


Other Language Servers in F#

With this, you should have enough information to add your own capabilities for things like auto-completion or inlay hints. However, this example is still only scratching the surface of writing a language server. Some other libraries that use F# (and the LanguageServerProtocol library shown here) to implement a language server are listed below which can help you to see how you could expand a language server to something truly expansive.

  • ProtoGraph: The programming language I have been working on
  • Marksman: A language server for markdown documents
  • FsAutoComplete: The language server for F# itself by Ionide

About

No description, website, or topics provided.

Resources

License

Stars

Watchers

Forks

Releases

No releases published

Packages

No packages published