Safe Haskell | None |
---|---|
Language | Haskell98 |
- makeSocket :: String -> Int -> IO Socket
- closeSocket :: Socket -> IO ()
- data PendingConnection
- makePendingConnection :: Socket -> IO PendingConnection
- pendingRequest :: PendingConnection -> RequestHead
- data AcceptRequest = AcceptRequest {}
- acceptRequest :: PendingConnection -> IO Connection
- acceptRequestWith :: PendingConnection -> AcceptRequest -> IO Connection
- rejectRequest :: PendingConnection -> ByteString -> IO ()
- data Connection
- data ConnectionOptions = ConnectionOptions {
- connectionOnPong :: IO ()
- defaultConnectionOptions :: ConnectionOptions
- receive :: Connection -> IO Message
- receiveDataMessage :: Connection -> IO DataMessage
- receiveData :: WebSocketsData a => Connection -> IO a
- send :: Connection -> Message -> IO ()
- sendDataMessage :: Connection -> DataMessage -> IO ()
- sendTextData :: WebSocketsData a => Connection -> a -> IO ()
- sendBinaryData :: WebSocketsData a => Connection -> a -> IO ()
- sendClose :: WebSocketsData a => Connection -> 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
- class WebSocketsData a where
- fromLazyByteString :: ByteString -> a
- toLazyByteString :: a -> ByteString
- data HandshakeException
- data ConnectionException
- type ServerApp = PendingConnection -> IO ()
- runServer :: String -> Int -> ServerApp -> IO ()
- runServerWith :: String -> Int -> ConnectionOptions -> ServerApp -> IO ()
- type ServerProgram = Connection -> StdOutMutex -> ConnectionSendMutex -> IO ()
- server :: String -> Int -> ServerProgram -> IO ()
- type StdOutMutex = Mutex [[Char]]
- safeSendText :: ConnectionSendMutex -> Connection -> Text -> IO ()
- safeSend :: ConnectionSendMutex -> Connection -> DataMessage -> IO ()
- type ConnectionSendMutex = Mutex ()
- 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 :: (InputStream ByteString, OutputStream ByteString) -> String -> String -> ConnectionOptions -> Headers -> ClientApp a -> IO a
Incoming connections and handshaking
makeSocket :: String -> Int -> IO Socket Source
Create a standardized socket. Should only be used for a quick and dirty solution! Should be preceded by the call Network.Socket.withSocketsDo
closeSocket :: Socket -> IO () Source
Closes a socket. This function serves as a quick utility to close a socket and as a reminder that you need to close sockets made by makeSocket.
data PendingConnection Source
A new client connected to the server. We haven't accepted the connection yet, though.
makePendingConnection :: Socket -> IO PendingConnection Source
Use data from the socket to create a Pending Connection. This is a blocking function. It tries to first accept a connection before creating a pending connection. Then you are able to choose if you want to accept the connection or not.
pendingRequest :: PendingConnection -> RequestHead Source
Useful for e.g. inspecting the request path.
data AcceptRequest Source
AcceptRequest | |
|
rejectRequest :: PendingConnection -> ByteString -> IO () Source
Main connection type
data Connection Source
Options for connections
Sending and receiving messages
receive :: Connection -> IO Message Source
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.
send :: Connection -> Message -> IO () Source
sendDataMessage :: Connection -> DataMessage -> IO () Source
Send a DataMessage
sendTextData :: WebSocketsData a => Connection -> a -> IO () Source
Send a message as text
sendBinaryData :: WebSocketsData a => Connection -> a -> IO () Source
Send a message as binary data
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.
sendPing :: WebSocketsData a => Connection -> a -> IO () Source
Send a ping
HTTP Types
type Headers = [(CI ByteString, ByteString)] Source
Request headers
data RequestHead Source
An HTTP request. The request body is not yet read.
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.
data ResponseHead Source
HTTP response, without body.
WebSocket message types
The kind of message a server application typically deals with
data ControlMessage Source
Different control messages
data DataMessage 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.
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
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 -> a Source
toLazyByteString :: a -> 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.
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"?) |
data ConnectionException Source
Various exceptions that can occur while receiving or transmitting messages
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. |
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.
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.
runServerWith :: String -> Int -> ConnectionOptions -> ServerApp -> IO () Source
A version of runServer
which allows you to customize some options.
Running a standalone Extended Server
type ServerProgram = Connection -> StdOutMutex -> ConnectionSendMutex -> IO () Source
type StdOutMutex = Mutex [[Char]] Source
safeSendText :: ConnectionSendMutex -> Connection -> Text -> IO () Source
safeSend :: ConnectionSendMutex -> Connection -> DataMessage -> IO () Source
type ConnectionSendMutex = Mutex () Source
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.
:: (InputStream ByteString, OutputStream ByteString) | Stream |
-> String | Host |
-> String | Path |
-> ConnectionOptions | Connection options |
-> Headers | Custom headers to send |
-> ClientApp a | Client application |
-> IO a |