Safe Haskell | None |
---|
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:
- data WebSocketsOptions = WebSocketsOptions {}
- defaultWebSocketsOptions :: WebSocketsOptions
- data WebSockets p a
- runWebSockets :: Protocol p => RequestHttpPart -> (Request -> WebSockets p a) -> Iteratee ByteString IO () -> Iteratee ByteString IO a
- runWebSocketsWith :: forall p a. Protocol p => WebSocketsOptions -> RequestHttpPart -> (Request -> WebSockets p a) -> Iteratee ByteString IO () -> Iteratee ByteString IO a
- runWebSocketsHandshake :: Protocol p => Bool -> (Request -> WebSockets p a) -> Iteratee ByteString IO () -> Iteratee ByteString IO a
- runWebSocketsWithHandshake :: Protocol p => WebSocketsOptions -> Bool -> (Request -> WebSockets p a) -> Iteratee ByteString IO () -> Iteratee ByteString IO a
- class Protocol p
- class Protocol p => TextProtocol p
- class TextProtocol p => BinaryProtocol p
- data Hybi00
- data Hybi10
- runServer :: Protocol p => String -> Int -> (Request -> WebSockets p ()) -> IO ()
- runWithSocket :: Protocol p => Socket -> (Request -> WebSockets p a) -> IO a
- type Headers = [(CI ByteString, ByteString)]
- data Request = Request {}
- data RequestHttpPart = RequestHttpPart {}
- data RequestBody = RequestBody RequestHttpPart ByteString
- data ResponseHttpPart = ResponseHttpPart {}
- data ResponseBody = ResponseBody ResponseHttpPart ByteString
- data Message p
- = ControlMessage (ControlMessage p)
- | DataMessage (DataMessage p)
- data ControlMessage p
- = Close ByteString
- | Ping ByteString
- | Pong ByteString
- data DataMessage p
- class WebSocketsData a where
- fromLazyByteString :: ByteString -> a
- toLazyByteString :: a -> ByteString
- acceptRequest :: Protocol p => Request -> WebSockets p ()
- rejectRequest :: Protocol p => Request -> String -> WebSockets p a
- getVersion :: Protocol p => WebSockets p String
- receive :: Protocol p => WebSockets p (Message p)
- receiveDataMessage :: Protocol p => WebSockets p (DataMessage p)
- receiveData :: (Protocol p, WebSocketsData a) => WebSockets p a
- send :: Protocol p => Message p -> WebSockets p ()
- sendTextData :: (TextProtocol p, WebSocketsData a) => a -> WebSockets p ()
- sendBinaryData :: (BinaryProtocol p, WebSocketsData a) => a -> WebSockets p ()
- data Sink p
- sendSink :: Sink p -> Message p -> IO ()
- getSink :: Protocol p => WebSockets p (Sink p)
- close :: (TextProtocol p, WebSocketsData a) => a -> Message p
- ping :: (BinaryProtocol p, WebSocketsData a) => a -> Message p
- pong :: (BinaryProtocol p, WebSocketsData a) => a -> Message p
- textData :: (TextProtocol p, WebSocketsData a) => a -> Message p
- binaryData :: (BinaryProtocol p, WebSocketsData a) => a -> Message p
- spawnPingThread :: BinaryProtocol p => Int -> WebSockets p ()
- throwWsError :: Exception e => e -> WebSockets p a
- catchWsError :: WebSockets p a -> (SomeException -> WebSockets p a) -> WebSockets p a
- data HandshakeError
- data ConnectionError
- connect :: Protocol p => String -> Int -> String -> WebSockets p a -> IO a
- connectWith :: Protocol p => String -> Int -> String -> Maybe String -> Maybe [String] -> WebSockets p a -> IO a
WebSocket type
defaultWebSocketsOptions :: WebSocketsOptionsSource
Default options
data WebSockets p a Source
The monad in which you can write WebSocket-capable applications
Monad (WebSockets p) | |
Functor (WebSockets p) | |
Functor (WebSockets p) => Applicative (WebSockets p) | |
Monad (WebSockets p) => MonadIO (WebSockets p) |
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 => TextProtocol p Source
TextProtocol Hybi00_ | |
TextProtocol Hybi10_ | |
TextProtocol Hybi00 | |
TextProtocol Hybi10 |
class TextProtocol p => BinaryProtocol p Source
BinaryProtocol Hybi10_ | |
BinaryProtocol Hybi10 |
A simple standalone server
:: 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
Full request type, including the response to it
data RequestBody Source
A request with a body
data ResponseBody Source
A response including a body
WebSockets types
The kind of message a server application typically deals with
data ControlMessage p Source
Different control messages
Eq (ControlMessage p) | |
Show (ControlMessage p) |
data DataMessage p Source
For an end-user of this library, dealing with Frame
s would be a bit
low-level. This is why define another type on top of it, which represents
data for the application layer.
Eq (DataMessage p) | |
Show (DataMessage p) |
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 theText
instance when you are sure that the data is UTF-8 encoded (which is the case forText
messages). - Messages can be very large. If this is the case, it might be inefficient to
use the strict
ByteString
andText
instances.
fromLazyByteString :: ByteString -> aSource
toLazyByteString :: a -> ByteStringSource
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
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
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.
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.
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. |