How to use servant-client with websockets?

I have a working Servant server and now I’d like to test it. The official guide suggests using servant-client. The example on the home page of servant-client here has some confusing syntax I’ve never seen before:

-- 'client' allows you to produce operations to query an API from a client.
postNewBook :: Book -> ClientM Book
getAllBooks :: ClientM [Book]
(getAllBooks :<|> postNewBook) = client myApi

I can’t understand how there can be multiple type signatures, followed by a single definition. But if I press on and just mimic the syntax, I can get the code to compile. That is until I include the websockets (ws) part of the API and handler:

type API = ...
      :<|> ...
      :<|> "api" :> "chat" :> Capture "chatId" Text :> WebSocket

WebSocket is from the servant-websockets package here.

I then write the testing code exactly the same way as before:

endpoint1 :: Text -> ClientM Text
endpoint2 :: Int -> ClientM Text
chatHandler :: Text -> ClientM WebSocket
( endpoint1 :<|> endpoint2 :<|> chatHandler ) = client api

But I’m hit with such an error:

    • Couldn't match type ‘servant-client-core-0.18.2:Servant.Client.Core.HasClient.Client
                             ClientM WebSocket’
                     with ‘ClientM WebSocket’
      Expected type: (LetterId -> ClientM LetterMeta)
                     :<|> ((Letter -> ClientM Text)
                           :<|> ((Text -> ClientM Text)
                                 :<|> ((Text -> ClientM Text)
                                       :<|> ((EntranceId -> ClientM Text)
                                             :<|> ((SpawnEntranceParams -> ClientM Text)
                                                   :<|> (Text -> ClientM WebSocket))))))
        Actual type: servant-client-core-0.18.2:Servant.Client.Core.HasClient.Client
                       ClientM API

Anyone has a clue about the strange syntax, and how to make servant-client work with websockets?

Unfortunately I can’t offer any help with the WebSockets, but hopefully I can help with the syntax.

Putting Servant aside for a moment, let’s see how you can have multiple type signatures followed by a single definition. Typically at the top level you have type definitions immediately followed by value definitions, like this:

one :: Int
one = 1

two :: Int
two = 2

But Haskell doesn’t require them to be arranged like that. You can re-order them however you’d like. For instance you could put all the type definitions at the top of the file as a sort of header, then put all the value definitions later on.

one :: Int
two :: Int

one = 1
two = 2

Another thing Haskell lets you do is pattern match on constructors when you assign values in a definition. Typically you’ll see this in case, let, or where expressions, but they can happen at the top level too. For example you can pattern match on a tuple:

(one, two) = (1, 2)

And of course you can keep the type signatures from before:

one :: Int
two :: Int
(one, two) = (1, 2)

Finally, the thing on the right side of the equals sign doesn’t need to be a literal. It can be an expression. And you can match any constructor on the left hand side as well. So something like this is perhaps more similar to what Servant’s doing:

one :: Int
two :: Int
( one : two : _rest ) = [ 1 .. ]
3 Likes

I’m able to understand everything up to the last part:

( one : two : _rest ) = [ 1.. ]

So one and two will be matched to 1 and 2, but what about _rest?
If I try to do show _rest, will it print an infinite list starting from 3?

Yes:

Prelude> (x1:x2:xs) = [1..]
Prelude> x1
1
Prelude> x2
2
Prelude> take 10 xs
[3,4,5,6,7,8,9,10,11,12]

Cool, thanks @taylorfausak and @jaror . I’m one step closer to figuring out the part with servant-client.

I’m not sure whether you can use servant-client with WebSockets. servant-websockets would need to implement HasClient typeclass, but I see that it only implements HasServer.

Anyway it would be a bit different from the normal client API. In the generated handler function you just statically pass all the arguments from the query and get a result in the ClientM monad. For the websocket you would need a handler of type similar to (Connection -> IO a) -> ClientM a, because you need to describe a whole interaction between your client and server.

I see that websockets package itself has some API to interact with servers. Perhaps you should take a look at it? If you need to use servant-client for the whole API then you can try to implement HasClient WebSocket itself, probably mimicking the HasClient Raw instance.

Thanks for the reply. So it is indeed what I’m suspecting, that servant-websockets doesn’t support the client-side of Servant yet. But I’m having a hard time to comprehend the rest of what’s going on. Mimicking HasClient m Raw sounds like the right idea, but I don’t know how it, or anything works yet, let alone how to mimick them. Client, ClientM, client, runClient, HasClient are really confusing me.

People say that Servant is harder than other frameworks due to its type machinery. My impression is that it’s not hard to just use it to write a server. Or to write a client for testing for a typical API. But the difficulty rises if I want to extend things a little.

I’ve read through implementing a mini Servant. In fact, I studied what are type families and type-level programming first, before getting into that. It still hasn’t fully made sense. I’m trying the Servant paper now. Maybe I just need to read them multiple times, or write a mini Servant myself?