| Safe Haskell | None | 
|---|---|
| Language | Haskell98 | 
Network.WebSockets
Contents
Synopsis
- data PendingConnection
- pendingRequest :: PendingConnection -> RequestHead
- acceptRequest :: PendingConnection -> IO Connection
- data AcceptRequest = AcceptRequest {- acceptSubprotocol :: !(Maybe ByteString)
- acceptHeaders :: !Headers
 
- defaultAcceptRequest :: AcceptRequest
- acceptRequestWith :: PendingConnection -> AcceptRequest -> IO Connection
- rejectRequest :: PendingConnection -> ByteString -> IO ()
- data RejectRequest = RejectRequest {- rejectCode :: !Int
- rejectMessage :: !ByteString
- rejectHeaders :: Headers
- rejectBody :: !ByteString
 
- defaultRejectRequest :: RejectRequest
- rejectRequestWith :: PendingConnection -> RejectRequest -> IO ()
- data Connection
- data ConnectionOptions = ConnectionOptions {}
- defaultConnectionOptions :: ConnectionOptions
- data CompressionOptions
- data PermessageDeflate = PermessageDeflate {}
- defaultPermessageDeflate :: PermessageDeflate
- data SizeLimit
- receive :: Connection -> IO Message
- receiveDataMessage :: Connection -> IO DataMessage
- receiveData :: WebSocketsData a => Connection -> IO a
- send :: Connection -> Message -> IO ()
- sendDataMessage :: Connection -> DataMessage -> IO ()
- sendDataMessages :: Connection -> [DataMessage] -> IO ()
- sendTextData :: WebSocketsData a => Connection -> a -> IO ()
- sendTextDatas :: WebSocketsData a => Connection -> [a] -> IO ()
- sendBinaryData :: WebSocketsData a => Connection -> a -> IO ()
- sendBinaryDatas :: WebSocketsData a => Connection -> [a] -> IO ()
- sendClose :: WebSocketsData a => Connection -> a -> IO ()
- sendCloseCode :: WebSocketsData a => Connection -> Word16 -> a -> IO ()
- sendPing :: WebSocketsData a => Connection -> a -> IO ()
- type Headers = [(CI ByteString, ByteString)]
- data Request = Request RequestHead ByteString
- data RequestHead = RequestHead {}
- getRequestSubprotocols :: RequestHead -> [ByteString]
- data Response = Response ResponseHead ByteString
- data ResponseHead = ResponseHead {}
- data Message
- data ControlMessage
- data DataMessage- = Text ByteString (Maybe Text)
- | Binary ByteString
 
- class WebSocketsData a where
- data HandshakeException
- data ConnectionException
- type ServerApp = PendingConnection -> IO ()
- runServer :: String -> Int -> ServerApp -> IO ()
- runServerWith :: String -> Int -> ConnectionOptions -> ServerApp -> IO ()
- makeListenSocket :: String -> Int -> IO Socket
- makePendingConnection :: Socket -> ConnectionOptions -> IO PendingConnection
- makePendingConnectionFromStream :: Stream -> ConnectionOptions -> IO PendingConnection
- type ClientApp a = Connection -> IO a
- runClient :: String -> Int -> String -> ClientApp a -> IO a
- runClientWith :: String -> Int -> String -> ConnectionOptions -> Headers -> ClientApp a -> IO a
- runClientWithSocket :: Socket -> String -> String -> ConnectionOptions -> Headers -> ClientApp a -> IO a
- runClientWithStream :: Stream -> String -> String -> ConnectionOptions -> Headers -> ClientApp a -> IO a
- newClientConnection :: Stream -> String -> String -> ConnectionOptions -> Headers -> IO Connection
- forkPingThread :: Connection -> Int -> IO ()
Incoming connections and handshaking
data PendingConnection Source #
A new client connected to the server. We haven't accepted the connection yet, though.
pendingRequest :: PendingConnection -> RequestHead Source #
Useful for e.g. inspecting the request path.
acceptRequest :: PendingConnection -> IO Connection Source #
Accept a pending connection, turning it into a Connection.
data AcceptRequest Source #
This datatype allows you to set options for acceptRequestWith.  It is
 strongly recommended to use defaultAcceptRequest and then modify the
 various fields, that way new fields introduced in the library do not break
 your code.
Constructors
| AcceptRequest | |
| Fields 
 | |
acceptRequestWith :: PendingConnection -> AcceptRequest -> IO Connection Source #
This function is like acceptRequest but allows you to set custom options
 using the AcceptRequest datatype.
Arguments
| :: PendingConnection | Connection to reject | 
| -> ByteString | Rejection response body | 
| -> IO () | 
data RejectRequest Source #
Parameters that allow you to tweak how a request is rejected.  Please use
 defaultRejectRequest and modify fields using record syntax so your code
 will not break when new fields are added.
Constructors
| RejectRequest | |
| Fields 
 | |
Arguments
| :: PendingConnection | Connection to reject | 
| -> RejectRequest | Params on how to reject the request | 
| -> IO () | 
Main connection type
data Connection Source #
Options for connections
data ConnectionOptions Source #
Set options for a Connection.  Please do not use this constructor
 directly, but rather use defaultConnectionOptions and then set the fields
 you want, e.g.:
myOptions = defaultConnectionOptions {connectionStrictUnicode = True}This way your code does not break if the library introduces new fields.
Constructors
| ConnectionOptions | |
| Fields 
 | |
defaultConnectionOptions :: ConnectionOptions Source #
The default connection options:
- Nothing happens when a pong is received.
- Compression is disabled.
- Lenient unicode decoding.
Compression options
data CompressionOptions Source #
Instances
| Eq CompressionOptions Source # | |
| Defined in Network.WebSockets.Connection.Options Methods (==) :: CompressionOptions -> CompressionOptions -> Bool # (/=) :: CompressionOptions -> CompressionOptions -> Bool # | |
| Show CompressionOptions Source # | |
| Defined in Network.WebSockets.Connection.Options Methods showsPrec :: Int -> CompressionOptions -> ShowS # show :: CompressionOptions -> String # showList :: [CompressionOptions] -> ShowS # | |
data PermessageDeflate Source #
Four extension parameters are defined for "permessage-deflate" to help endpoints manage per-connection resource usage.
- "server_no_context_takeover"
- "client_no_context_takeover"
- "server_max_window_bits"
- "client_max_window_bits"
Constructors
| PermessageDeflate | |
| Fields | |
Instances
| Eq PermessageDeflate Source # | |
| Defined in Network.WebSockets.Connection.Options Methods (==) :: PermessageDeflate -> PermessageDeflate -> Bool # (/=) :: PermessageDeflate -> PermessageDeflate -> Bool # | |
| Show PermessageDeflate Source # | |
| Defined in Network.WebSockets.Connection.Options Methods showsPrec :: Int -> PermessageDeflate -> ShowS # show :: PermessageDeflate -> String # showList :: [PermessageDeflate] -> ShowS # | |
Protection limits
A size limit, in bytes.  The Monoid instance takes the minimum limit.
Constructors
| NoSizeLimit | |
| SizeLimit !Int64 | 
Sending and receiving messages
receiveDataMessage :: Connection -> IO DataMessage Source #
Receive an application message. Automatically respond to control messages.
When the peer sends a close control message, an exception of type CloseRequest
 is thrown.  The peer can send a close control message either to initiate a
 close or in response to a close message we have sent to the peer.  In either
 case the CloseRequest exception will be thrown.  The RFC specifies that
 the server is responsible for closing the TCP connection, which should happen
 after receiving the CloseRequest exception from this function.
This will throw ConnectionClosed if the TCP connection dies unexpectedly.
receiveData :: WebSocketsData a => Connection -> IO a Source #
Receive a message, converting it to whatever format is needed.
sendDataMessage :: Connection -> DataMessage -> IO () Source #
Send a DataMessage.  This allows you send both human-readable text and
 binary data.  This is a slightly more low-level interface than sendTextData
 or sendBinaryData.
sendDataMessages :: Connection -> [DataMessage] -> IO () Source #
Send a collection of DataMessages.  This is more efficient than calling
 sendDataMessage many times.
sendTextData :: WebSocketsData a => Connection -> a -> IO () Source #
Send a textual message. The message will be encoded as UTF-8. This should be the default choice for human-readable text-based protocols such as JSON.
sendTextDatas :: WebSocketsData a => Connection -> [a] -> IO () Source #
Send a number of textual messages.  This is more efficient than calling
 sendTextData many times.
sendBinaryData :: WebSocketsData a => Connection -> a -> IO () Source #
Send a binary message. This is useful for sending binary blobs, e.g. images, data encoded with MessagePack, images...
sendBinaryDatas :: WebSocketsData a => Connection -> [a] -> IO () Source #
Send a number of binary messages.  This is more efficient than calling
 sendBinaryData many times.
sendClose :: WebSocketsData a => Connection -> a -> IO () Source #
Send a friendly close message.  Note that after sending this message,
 you should still continue calling receiveDataMessage to process any
 in-flight messages.  The peer will eventually respond with a close control
 message of its own which will cause receiveDataMessage to throw the
 CloseRequest exception.  This exception is when you can finally consider
 the connection closed.
sendCloseCode :: WebSocketsData a => Connection -> Word16 -> a -> IO () Source #
Send a friendly close message and close code.  Similar to sendClose,
 you should continue calling receiveDataMessage until you receive a
 CloseRequest exception.
See http://tools.ietf.org/html/rfc6455#section-7.4 for a list of close codes.
sendPing :: WebSocketsData a => Connection -> a -> IO () Source #
Send a ping
HTTP Types
type Headers = [(CI ByteString, ByteString)] Source #
Request headers
A request with a body
Constructors
| Request RequestHead ByteString | 
data RequestHead Source #
An HTTP request. The request body is not yet read.
Constructors
| RequestHead | |
| Fields 
 | |
Instances
| Show RequestHead Source # | |
| Defined in Network.WebSockets.Http Methods showsPrec :: Int -> RequestHead -> ShowS # show :: RequestHead -> String # showList :: [RequestHead] -> ShowS # | |
getRequestSubprotocols :: RequestHead -> [ByteString] Source #
List of subprotocols specified by the client, in order of preference. If the client did not specify a list of subprotocols, this will be the empty list.
A response including a body
Constructors
| Response ResponseHead ByteString | 
data ResponseHead Source #
HTTP response, without body.
Constructors
| ResponseHead | |
| Fields 
 | |
Instances
| Show ResponseHead Source # | |
| Defined in Network.WebSockets.Http Methods showsPrec :: Int -> ResponseHead -> ShowS # show :: ResponseHead -> String # showList :: [ResponseHead] -> ShowS # | |
WebSocket message types
The kind of message a server application typically deals with
Constructors
| ControlMessage ControlMessage | |
| DataMessage Bool Bool Bool DataMessage | Reserved bits, actual message | 
data ControlMessage Source #
Different control messages
Constructors
| Close Word16 ByteString | |
| Ping ByteString | |
| Pong ByteString | 
Instances
| Eq ControlMessage Source # | |
| Defined in Network.WebSockets.Types Methods (==) :: ControlMessage -> ControlMessage -> Bool # (/=) :: ControlMessage -> ControlMessage -> Bool # | |
| Show ControlMessage Source # | |
| Defined in Network.WebSockets.Types Methods showsPrec :: Int -> ControlMessage -> ShowS # show :: ControlMessage -> String # showList :: [ControlMessage] -> ShowS # | |
data DataMessage 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.
There are currently two kinds of data messages supported by the WebSockets protocol:
- Textual UTF-8 encoded data. This corresponds roughly to sending a String in JavaScript.
- Binary data. This corresponds roughly to send an ArrayBuffer in JavaScript.
Constructors
| Text ByteString (Maybe Text) | A textual message. The second field might contain the decoded UTF-8 text for caching reasons. This field is computed lazily so if it's not accessed, it should have no performance impact. | 
| Binary ByteString | A binary message. | 
Instances
| Eq DataMessage Source # | |
| Defined in Network.WebSockets.Types | |
| Show DataMessage Source # | |
| Defined in Network.WebSockets.Types Methods showsPrec :: Int -> DataMessage -> ShowS # show :: DataMessage -> String # showList :: [DataMessage] -> ShowS # | |
class WebSocketsData a where Source #
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 Textor theTextinstance when you are sure that the data is UTF-8 encoded (which is the case forTextmessages).
- Messages can be very large. If this is the case, it might be inefficient to
   use the strict ByteStringandTextinstances.
Minimal complete definition
Methods
fromDataMessage :: DataMessage -> a Source #
fromLazyByteString :: ByteString -> a Source #
toLazyByteString :: a -> ByteString Source #
Instances
| WebSocketsData ByteString Source # | |
| Defined in Network.WebSockets.Types Methods fromDataMessage :: DataMessage -> ByteString Source # | |
| WebSocketsData ByteString Source # | |
| Defined in Network.WebSockets.Types Methods fromDataMessage :: DataMessage -> ByteString Source # | |
| WebSocketsData Text Source # | |
| Defined in Network.WebSockets.Types Methods fromDataMessage :: DataMessage -> Text Source # fromLazyByteString :: ByteString -> Text Source # toLazyByteString :: Text -> ByteString Source # | |
| WebSocketsData Text Source # | |
| Defined in Network.WebSockets.Types Methods fromDataMessage :: DataMessage -> Text Source # fromLazyByteString :: ByteString -> Text Source # toLazyByteString :: Text -> ByteString Source # | |
Exceptions
data HandshakeException Source #
Error in case of failed handshake. Will be thrown as an Exception.
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 RequestHead String | The request was somehow invalid (missing headers or wrong security token) | 
| MalformedResponse ResponseHead 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") | 
| OtherHandshakeException String | for example "EOF came too early" (which is actually a parse error) or for your own errors. (like "unknown path"?) | 
Instances
| Show HandshakeException Source # | |
| Defined in Network.WebSockets.Http Methods showsPrec :: Int -> HandshakeException -> ShowS # show :: HandshakeException -> String # showList :: [HandshakeException] -> ShowS # | |
| Exception HandshakeException Source # | |
| Defined in Network.WebSockets.Http Methods toException :: HandshakeException -> SomeException # fromException :: SomeException -> Maybe HandshakeException # | |
data ConnectionException Source #
Various exceptions that can occur while receiving or transmitting messages
Constructors
| CloseRequest Word16 ByteString | The peer has requested that the connection be closed, and included a close code and a reason for closing. When receiving this exception, no more messages can be sent. Also, the server is responsible for closing the TCP connection once this exception is received. See http://tools.ietf.org/html/rfc6455#section-7.4 for a list of close codes. | 
| ConnectionClosed | The peer unexpectedly closed the connection while we were trying to receive some data. This is a violation of the websocket RFC since the TCP connection should only be closed after sending and receiving close control messages. | 
| ParseException String | The client sent garbage, i.e. we could not parse the WebSockets stream. | 
| UnicodeException String | The client sent invalid UTF-8. Note that this exception will only be thrown if strict decoding is set in the connection options. | 
Instances
| Eq ConnectionException Source # | |
| Defined in Network.WebSockets.Types Methods (==) :: ConnectionException -> ConnectionException -> Bool # (/=) :: ConnectionException -> ConnectionException -> Bool # | |
| Show ConnectionException Source # | |
| Defined in Network.WebSockets.Types Methods showsPrec :: Int -> ConnectionException -> ShowS # show :: ConnectionException -> String # showList :: [ConnectionException] -> ShowS # | |
| Exception ConnectionException Source # | |
| Defined in Network.WebSockets.Types Methods toException :: ConnectionException -> SomeException # fromException :: SomeException -> Maybe ConnectionException # | |
Running a standalone server
type ServerApp = PendingConnection -> IO () Source #
WebSockets application that can be ran by a server. Once this IO action
 finishes, the underlying socket is closed automatically.
Arguments
| :: String | Address to bind | 
| -> Int | Port to listen on | 
| -> ServerApp | Application | 
| -> IO () | Never returns | 
Provides a simple server. This function blocks forever. Note that this is merely provided for quick-and-dirty or internal applications, but for real applications, you should use a real server.
For example:
- Performance is reasonable under load, but:
- No protection against DoS attacks is provided.
- No logging is performed.
- ...
Glue for using this package with real servers is provided by:
runServerWith :: String -> Int -> ConnectionOptions -> ServerApp -> IO () Source #
A version of runServer which allows you to customize some options.
Utilities for writing your own server
makeListenSocket :: String -> Int -> IO Socket Source #
Create a standardized socket on which you can listen for incomming
 connections. Should only be used for a quick and dirty solution! Should be
 preceded by the call withSocketsDo.
makePendingConnection :: Socket -> ConnectionOptions -> IO PendingConnection Source #
Turns a socket, connected to some client, into a PendingConnection. The
 PendingConnection should be closed using close later.
makePendingConnectionFromStream :: Stream -> ConnectionOptions -> IO PendingConnection Source #
More general version of makePendingConnection for Stream
 instead of a Socket.
Running a client
type ClientApp a = Connection -> IO a Source #
A client application interacting with a single server. Once this IO
 action finished, the underlying socket is closed automatically.
Arguments
| :: Stream | Stream that will be used by the new  | 
| -> String | Host | 
| -> String | Path | 
| -> ConnectionOptions | Connection options | 
| -> Headers | Custom headers to send | 
| -> IO Connection | 
Build a new Connection from the client's point of view.
WARNING: Be sure to call close on the given Stream after you are
 done using the Connection in order to properly close the communication
 channel. runClientWithStream handles this for you, prefer to use it when
 possible.
Utilities
forkPingThread :: Connection -> Int -> IO () Source #
Forks a ping thread, sending a ping message every n seconds over the
 connection. The thread dies silently if the connection crashes or is closed.
This is useful to keep idle connections open through proxies and whatnot. Many (but not all) proxies have a 60 second default timeout, so based on that sending a ping every 30 seconds is a good idea.