websockets-0.7.0.1: A sensible and clean way to write WebSocket-capable servers in Haskell.

Safe HaskellNone

Network.WebSockets

Contents

Description

How do you use this library? Here's how:

Get an enumerator/iteratee pair from your favorite web server (or use a library which provides integration). Alternatively, use runServer to set up a simple standalone server.

An application typically has the form of I.Request -> I.WebSockets p (). The first thing to do is accept or reject the request, usually based upon the path in the Request. An example:

 {-# LANGUAGE OverloadedStrings #-}
 import Network.WebSockets

 app :: Protocol p => Request -> WebSockets p ()
 app rq = case requestPath rq of
    "/forbidden" -> rejectRequest rq "Forbidden!"
    _            -> do
        acceptRequest rq
        ... actual application ...

You can now start using the socket for sending and receiving data. But what's with the p in WebSockets p ()?

Well, the answer is that this library aims to support many versions of the WebSockets protocol. Unfortunately, not all versions of the protocol have the same capabilities: for example, older versions are not able to send binary data.

The library user (you!) choose which capabilities you need. Then, the browser and library will negotiate at runtime which version will be actually used.

As an example, here are two applications which need different capabilities:

 import Network.WebSockets
 import qualified Data.ByteString as B
 import qualified Data.Text as T
 
 app1 :: TextProtocol p => WebSockets p ()
 app1 = sendTextData (T.pack "Hello world!")
 
 app2 :: BinaryProtocol p => WebSockets p ()
 app2 = sendBinaryData (B.pack [0 .. 100])

When you tie the knot, you will need to decide what protocol to use, to prevent ambiguousness. A good rule of thumb is to select the lowest protocol possible, since higher versions are generally backwards compatible in terms of features. . For example, the following application uses only features from Hybi00, and is therefore compatible with Hybi10 and later protocols.

 app :: Request -> WebSockets Hybi00 ()
 app _ = app1
 
 main :: IO ()
 main = runServer "0.0.0.0" 8000 app

In some cases, you want to escape from the WebSockets monad and send data to the websocket from different threads. To this end, the getSink method is provided. The next example spawns a thread which continuously spams the client in another thread:

 import Control.Concurrent (forkIO)
 import Control.Monad (forever)
 import Control.Monad.Trans (liftIO)
 import Network.WebSockets
 import qualified Data.Text as T
 
 spam :: TextProtocol p => WebSockets p ()
 spam = do
     sink <- getSink
     _ <- liftIO $ forkIO $ forever $
         sendSink sink $ textData (T.pack "SPAM SPAM SPAM!")
     sendTextData (T.pack "Hello world!")

For safety reasons, you can only read from the socket in the WebSockets monad.

For a full example, see:

http://jaspervdj.be/websockets/example.html

Synopsis

WebSocket type

data WebSocketsOptions Source

Options for the WebSocket program

Constructors

WebSocketsOptions 

Fields

onPong :: IO ()
 

data WebSockets p a Source

The monad in which you can write WebSocket-capable applications

runWebSockets :: Protocol p => RequestHttpPart -> (Request -> WebSockets p a) -> Iteratee ByteString IO () -> Iteratee ByteString IO aSource

Run a WebSockets application on an 'Enumerator'/'Iteratee' pair, given that you (read: your web server) has already received the HTTP part of the initial request. If not, you might want to use runWebSocketsWithHandshake instead.

If the handshake failed, throws a HandshakeError. Otherwise, executes the supplied continuation. You should still send a response to the client yourself.

runWebSocketsWith :: forall p a. Protocol p => WebSocketsOptions -> RequestHttpPart -> (Request -> WebSockets p a) -> Iteratee ByteString IO () -> Iteratee ByteString IO aSource

Version of runWebSockets which allows you to specify custom options

runWebSocketsHandshake :: Protocol p => Bool -> (Request -> WebSockets p a) -> Iteratee ByteString IO () -> Iteratee ByteString IO aSource

Receives the initial client handshake, then behaves like runWebSockets.

runWebSocketsWithHandshake :: Protocol p => WebSocketsOptions -> Bool -> (Request -> WebSockets p a) -> Iteratee ByteString IO () -> Iteratee ByteString IO aSource

Receives the initial client handshake, then behaves like runWebSocketsWith.

Protocol versions

class Protocol p Source

Instances

A simple standalone server

runServerSource

Arguments

:: Protocol p 
=> String

Address to bind to

-> Int

Port to listen on

-> (Request -> WebSockets p ())

Application to serve

-> IO ()

Never returns

Provides a simple server. This function blocks forever. Note that this is merely provided for quick-and-dirty standalone applications, for real applications, you should use a real server.

runWithSocket :: Protocol p => Socket -> (Request -> WebSockets p a) -> IO aSource

This function wraps runWebSockets in order to provide a simple API for stand-alone servers.

HTTP Types

type Headers = [(CI ByteString, ByteString)]Source

Request headers

data Request Source

Full request type, including the response to it

Instances

data RequestHttpPart Source

(Internally used) HTTP headers and requested path.

data RequestBody Source

A request with a body

Instances

data ResponseBody Source

A response including a body

Instances

WebSockets types

data Message p Source

The kind of message a server application typically deals with

Instances

Eq (Message p) 
Show (Message p) 

data ControlMessage p Source

Different control messages

Instances

data DataMessage p Source

For an end-user of this library, dealing with Frames would be a bit low-level. This is why define another type on top of it, which represents data for the application layer.

Instances

class WebSocketsData a whereSource

In order to have an even more high-level API, we define a typeclass for values the user can receive from and send to the socket. A few warnings apply:

  • Natively, everything is represented as a ByteString, so this is the fastest instance
  • You should only use the Text or the Text instance when you are sure that the data is UTF-8 encoded (which is the case for Text messages).
  • Messages can be very large. If this is the case, it might be inefficient to use the strict ByteString and Text instances.

Handshake

acceptRequest :: Protocol p => Request -> WebSockets p ()Source

Accept a request. After this, you can start sending and receiving data.

rejectRequest :: Protocol p => Request -> String -> WebSockets p aSource

Reject a request, sending a 400 (Bad Request) to the client and throwing a RequestRejected (HandshakeError)

Various

getVersion :: Protocol p => WebSockets p StringSource

Find out the WebSockets version used at runtime

Receiving

receive :: Protocol p => WebSockets p (Message p)Source

Receive a message

receiveDataMessage :: Protocol p => WebSockets p (DataMessage p)Source

Receive an application message. Automatically respond to control messages.

receiveData :: (Protocol p, WebSocketsData a) => WebSockets p aSource

Receive a message, treating it as data transparently

Sending

send :: Protocol p => Message p -> WebSockets p ()Source

Low-level sending with an arbitrary Message

sendTextData :: (TextProtocol p, WebSocketsData a) => a -> WebSockets p ()Source

Send a text message

sendBinaryData :: (BinaryProtocol p, WebSocketsData a) => a -> WebSockets p ()Source

Send some binary data

Asynchronous sending

data Sink p Source

Used for asynchronous sending.

sendSink :: Sink p -> Message p -> IO ()Source

Send a message to a sink. Might generate an exception if the underlying connection is closed.

getSink :: Protocol p => WebSockets p (Sink p)Source

In case the user of the library wants to do asynchronous sending to the socket, he can extract a Sink and pass this value around, for example, to other threads.

close :: (TextProtocol p, WebSocketsData a) => a -> Message pSource

Construct a close message

ping :: (BinaryProtocol p, WebSocketsData a) => a -> Message pSource

Construct a ping message

pong :: (BinaryProtocol p, WebSocketsData a) => a -> Message pSource

Construct a pong message

textData :: (TextProtocol p, WebSocketsData a) => a -> Message pSource

Construct a text message

binaryData :: (BinaryProtocol p, WebSocketsData a) => a -> Message pSource

Construct a binary message

spawnPingThread :: BinaryProtocol p => Int -> WebSockets p ()Source

spawnPingThread n spawns a thread which sends a ping every n seconds (if the protocol supports it). To be called after having sent the response.

Error Handling

throwWsError :: Exception e => e -> WebSockets p aSource

Throw an iteratee error in the WebSockets monad

catchWsError :: WebSockets p a -> (SomeException -> WebSockets p a) -> WebSockets p aSource

Catch an iteratee error in the WebSockets monad

data HandshakeError Source

Error in case of failed handshake. Will be thrown as an iteratee exception. (Error condition).

TODO: This should probably be in the Handshake module, and is solely here to prevent a cyclic dependency.

Constructors

NotSupported

We don't have a match for the protocol requested by the client. todo: version parameter

MalformedRequest RequestHttpPart String

The request was somehow invalid (missing headers or wrong security token)

MalformedResponse ResponseHttpPart String

The servers response was somehow invalid (missing headers or wrong security token)

RequestRejected Request String

The request was well-formed, but the library user rejected it. (e.g. unknown path)

OtherHandshakeError String

for example EOF came too early (which is actually a parse error) or for your own errors. (like unknown path?)

data ConnectionError Source

The connection couldn't be established or broke down unexpectedly. thrown as an iteratee exception.

Constructors

ParseError ParseError

The client sent malformed data.

ConnectionClosed

the client closed the connection while we were trying to receive some data.

todo: Also want this for sending.

WebSockets Client

connectSource

Arguments

:: Protocol p 
=> String

Host

-> Int

Port

-> String

Path

-> WebSockets p a

Client application

-> IO a 

connectWithSource

Arguments

:: Protocol p 
=> String

Host

-> Int

Port

-> String

Path

-> Maybe String

Origin, if Nothing then server interprets connection as not coming from a browser.

-> Maybe [String]

Protocol List

-> WebSockets p a

Client application

-> IO a