⚗️ lsp-test

Posted on August 12, 2018

My Haskell Summer of Code project, lsp-test, is now available via Hackage. It's a framework for writing end-to-end tests for LSP servers, made for testing haskell-ide-engine.

But it's not just limited to haskell-ide-engine: It's language agnostic and works with any server that conforms to the Language Server Protocol. In fact lsp-test is basically a client that you can programmatically control. You specify what messages you want to send to the server, and check that the responses you get back are what you expected.

What does it look like?

runSession :: String -> ClientCapabilities -> FilePath -> Session a -> IO a

main = runSession "hie" fullCaps "proj/dir" $ do
  doc <- openDoc "Foo.hs" "haskell"
  getDocumentSymbols doc >>= liftIO putStrLn

Each test is encapsulated by a Session: a client-server connection from start to finish. Here we pass in the command to start the server, the capabilities that the client should declare and the root directory that the session should take place in. (fullCaps is a convenience function that declares all the latest features in the LSP specification)

Once you're inside a Session you're free to poke and talk away to your server.

You might have noticed that the example above didn't send an initialize request - Session takes care of this and some other laborious parts of the process:

  • Sending initialize requests with the correct process ID and capabilities
  • Generating and incrementing message ids
  • Keeping track of documents through workspace/applyEdit requests

There's also a Smörgåsbord of functions available for performing common tasks, such as getting a definition or checking the current diagnostics.

The message level

Most of the time you'll want to want to write your tests using these helper functions, but in case you're looking to do something more specific, you can drop down to a lower level and work with the individual messages that are sent and received.

The venerable request allows you to send any request defined in haskell-lsp-types, and will spit back the response for it. Most of the helper functions are implemented in terms of this.

request :: (ToJSON params, FromJSON a) => ClientMethod -> params -> Session (ResponseMessage a)

runSession "hie" fullCaps "my/dir" = do
  doc <- openDoc "Foo.hs" "haskell"
  let params = DocumentSymbolParams doc
  -- send and wait for the response
  rsp <- request TextDocumentDocumentSymbol params

You can also use the send family of functions if you don't want to wait for a response.

sendRequest :: ToJSON params => ClientMethod -> params -> Session LspId	
sendNotification :: ToJSON a => ClientMethod -> a -> Session ()
sendResponse :: ToJSON a => ResponseMessage a -> Session ()

Inside Session

This is where lsp-test's little breakthrough comes in: The Session monad is actually just a conduit parser that operates on individual messages.

type Session = ConduitParser FromServerMessage IO

runSession f = runConduit $ source .| runConduitParser f
  where
    source = getNextMessage handle >>= yield >> source

Incoming messages from the server are parsed in a stream. You specify the messages you expect to receive from the server in order, in between the messages you send to it.

-- get a specific response
msg1 <- message :: Session RspDocumentSymbols
-- get any request
msg2 <- anyRequest
sendRequest TextDocumentDocumentSymbol params
-- get a logging notification
msg3 <- loggingNotification

It has it's own version of satisfy that works on messages, which custom parser combinators are built up upon.

satisfy :: (FromServerMessage -> Bool) -> Session FromServerMessage
satisfy pred = do
  x <- await
  if pred x
    then return x
    else empty

loggingNotification = satisfy test
  where
    test (NotLogMessage _) = True
    test (NotShowMessage _) = True
    test (ReqShowMessage _) = True
    test _ = False

Whenever it's unable to parse a sequence of messages, it throws an exception, which can be used to make assertions about the messages that arrive.

But the great part is that it works with backtracking, and all your favourite combinators. So you can be as specific or as general as you'd like when describing the expected interaction with the server.

skipManyTill loggingNotification publishDiagnosticsNotification
count 4 (message :: Session ApplyWorkspaceEditRequest)
anyRequest <|> anyResponse

Building up a test suite

Other than throwing exceptions when it's unable to parse the incoming sequence of messages, lsp-test doesn't help you make assertions, so you are free to use whatever testing framework you like. In haskell-ide-engine, lsp-test is paired quite nicely with HSpec. Here's an excerpt from some tests for goto definition requests:

spec :: Spec
spec = describe "definitions" $ do
  it "goto's symbols" $ runSession hieCommand fullCaps "test/testdata" $ do
    doc <- openDoc "References.hs" "haskell"
    defs <- getDefinitions doc (Position 7 8)
    let expRange = Range (Position 4 0) (Position 4 3)
    liftIO $ defs `shouldBe` [Location (doc ^. uri) expRange]

  it "goto's imported modules" $ runSession hieCommand fullCaps "test/testdata/definition" $ do
    doc <- openDoc "Foo.hs" "haskell"
    defs <- getDefinitions doc (Position 2 8)
    liftIO $ do
      fp <- canonicalizePath "test/testdata/definition/Bar.hs"
      defs `shouldBe` [Location (filePathToUri fp) zeroRange]

Replaying

If your language server was built with haskell-lsp, you can use its built in capture format to take advantage of Language.Haskell.LSP.Test.Replay. This module replays captured sessions and ensures that the response from the server matches up with what it received during the original capture. In haskell-ide-engine you can capture a session to a file by launching the server with the --capture flag.

hie -c session.log

To test it with lsp-test, place the file as session.log inside a directory that mirrors the contents of the project root.

projectRoot
    ├── proj.cabal
    ├── src
    │   └── ...
    └── session.log

And then test it with replaySession.

replaySession "hie" "projectRoot"

lsp-test is smart enough to swap out the absolute URIs, so if you originally captured the scenario under /foo/bar/proj but then replay it at /test/foo, /foo/bar/proj/file.hs will get swapped as /test/foo/file.hs.

It also relaxes some "common-sense" checks:

  • Logging messages are ignored
  • The order of notifications in between requests and responses doesn't matter
  • It takes into account uniqued command IDs

If the interaction doesn't match up, you'll get nice pretty printed JSON of what was received, what was expected, and the diff between the two2.

This is useful if you want to test for regressions, or if there is some very specific behaviour that would be difficult to describe programmatically.

What's next?

DSL

Currently if you want to use lsp-tests to write tests, you need to write Haskell. There has been some experimenting in writing a custom DSL for describing tests.

"start" { wait for any then open "Test.hs" "haskell" }
"get the symbols" {
  wait for
    method == "textDocument/publishDiagnostics"
  then
    open "Test.hs" "haskell"
    id1: request "textDocument/documentSymbol" {
      textDocument: {
        uri: uri "Test.hs"
      }
    }
}
"check the symbols" {
  wait for
    id == 1
  then
    open "Test.hs" "haskell"
}

However, it may be more attractive to use dhall, a configuration language that ties in nicely with Haskell.

The ultimate aim is that lsp-test will be available as an executable binary (via cabal install/stack install/apt install), which can read and run tests from a file via the command line.

lsp-test test myTest.dhall

This would mean that servers implemented in languages other than Haskell can easily hook this into their CI without having to have a Haskell environment setup.

Finite state machine and fuzzy testing

My mentor pointed out that the interaction between the client and server during a Session could be described as a Mealy machine. The state-transition function waits for the next message from the client whilst the output function sends messages to the server.

data State = Initialize
           | WaitForDiagnostics
           | MakeSymbolRequest
           | Done 
wait :: FromServerMessage -> State -> State
send :: State -> FromServerMessage -> FromClientMessage

This led me to create a proof of concept that integrated with hedgehog. Hedgehog is a property based testing system a-la QuickCheck, but it also provides state machine testing.

I had to first tweak the Session monad to become a SessionT transformer and make it an instance of MonadTest and MonadThrow1 before it could be used.

type PropertySession = SessionT (PropertyT IO)

instance MonadThrow m => MonadCatch (SessionT m) where
  catch f h = f

instance MonadTest PropertySession where
  liftTest = lift . liftTest

And then the states could be described in terms of its pre-conditions, updates and post-conditions.

data OpenDoc (v :: * -> *) = OpenDoc
  deriving (Eq, Show)

instance HTraversable OpenDoc where
  htraverse _ OpenDoc = pure OpenDoc

s_openDoc_init :: (Monad n) => Command n PropertySession ModelState
s_openDoc_init =
  let gen TDocClose = Just $ pure OpenDoc
      gen _         = Nothing
      execute OpenDoc = openDoc "Foo.hs" "haskell"
  in Command gen execute [
      Require $ \s OpenDoc -> s == TDocClose
    , Update $ \_s OpenDoc o -> TDocOpen
    , Ensure $ \before after OpenDoc o -> do
        before === TDocClose
        let L.TextDocumentIdentifier uri = o
        uri === L.Uri "Foo.hs"
        after === TDocOpen
    ]

Once you describe a bunch of different states, you can then throw them into hedgehog and it will run them in random orders: Giving you fuzzy testing!

Fuzzy testing

Lessons learnt

The best way to get a taste for an API is by using it!

By using it to write tests for haskell-ide-engine at an early stage in development, it allowed me to figure out the sticking points and refine the ergonomics. For example, the client capabilities used to be set inside SessionConfig. But when testing for backwards compatibility, it quickly became evident that it needed to be more explicit, hence why it was moved to runSession.

If I was to start this project again, I would have focused a lot more on the DSL. Although language agnosticism was part the design, not including an easy way for non-Haskell environments to run tests was a major oversight. But with the framework in place, I am confident that we will be able to implement this soon.

It's also important to note that this past summer wasn't spent solely on lsp-test, and I invested a large amount of work into haskell-ide-engine as well. I would happily say that lsp-test paid off while doing this work: it helped catch a lot of regressions while doing extensive refactoring and development around the dispatcher, code actions and plugin infrastructure, not to mention the peace of mind from having a robust test-suite in place.

Thanks to my mentor Alan Zimmerman for all his help, and all the community at #haskell-ide-engine and #haskell for putting up with all my stupid questions. If you're developing a language and want to write an LSP server, consider giving lsp-test a shot, and let me know!

  1. As you can see, this is clearly not the right way to implement MonadThrow. If you do know how to for a continuation based monad, please let me know!
  2. Pro-tip: use the diff to incrementally update your session.log files if your expected output has changed.