Safe Haskell | None |
---|---|
Language | Haskell2010 |
- initialize :: IO EngineIO
- handler :: MonadIO m => EngineIO -> (Socket -> m SocketApp) -> ServerAPI m -> m ()
- data EngineIO
- data ServerAPI m = ServerAPI {
- srvGetQueryParams :: m (HashMap ByteString [ByteString])
- srvTerminateWithResponse :: Int -> ByteString -> Builder -> forall a. m a
- srvParseRequestBody :: forall a. Parser a -> m (Either String a)
- srvGetRequestMethod :: m ByteString
- srvRunWebSocket :: ServerApp -> m ()
- data SocketApp = SocketApp {
- saApp :: IO ()
- saOnDisconnect :: IO ()
- send :: Socket -> PacketContent -> STM ()
- receive :: Socket -> STM PacketContent
- data Socket
- type SocketId = ByteString
- socketId :: Socket -> SocketId
- getOpenSockets :: EngineIO -> STM (HashMap SocketId Socket)
- dupRawReader :: Socket -> IO (STM Packet)
- data Packet = Packet !PacketType !PacketContent
- parsePacket :: Parser Packet
- encodePacket :: Bool -> Packet -> Builder
- data PacketType
- data PacketContent
- newtype Payload = Payload (Vector Packet)
- parsePayload :: Parser Payload
- encodePayload :: Bool -> Payload -> Builder
- data TransportType
- parseTransportType :: Text -> Maybe TransportType
Documentation
Network.EngineIO
is a Haskell of implementation of
Engine.IO, a realtime framework for
the web. Engine.IO provides you with an abstraction for doing real-time
communication between a server and a client. Engine.IO abstracts the framing and
transport away, so that you can have real-time communication over long-polling
HTTP requests, which are later upgraded to web sockets, if available.
Network.EngineIO
needs to be provided with a ServerAPI
in order to be
ran. ServerAPI
informs us how to fetch request headers, write HTTP responses
to the client, and run web socket applications. Hackage contains implementations
of ServerAPI
as:
- engine-io-snap for Snap.
- engine-io-yesod for Yesod.
If you write your own implementation of ServerAPI
, please share it on Hackage
and I will link to it from here.
Example Usage
A simple echo server is easy to write with Engine.IO. The following imports will be required:
import Control.Concurrent.STM import Control.Monad (forever) import Network.EngineIO import Network.EngineIO.Snap import Snap.Http.Server
Next, we write the implementation of our per-socket processing logic. For this
application we simply receive from the socket, and then send the result back to
the socket. We wrap this all in forever
as this connection
should never terminate.
handleSocket :: Socket -> IO () handleSocket s = forever $ atomically $ receive s >>= send s
Finally, we add a main
function to our application to launch it. I'll use
engine-io-snap
as my server implementation:
main :: IO () main = do eio <- initialize quickHttpServe $ handler eio handleSocket
This means that any URL works as the Engine.IO server, which is sufficient for
our example. In a real production application, you will probably want to nest
the handler
under /engine.io
.
Running Engine.IO applications
initialize :: IO EngineIO Source
initialize
initializes a new Engine.IO server. You can later serve this
session by using handler
.
handler :: MonadIO m => EngineIO -> (Socket -> m SocketApp) -> ServerAPI m -> m () Source
Build the necessary handler for Engine.IO. The result of this function is a
computation that you should serve under the engine.io
path.
handler
takes a function as an argument that is called every time a new
session is created. This function runs in the m
monad, so you have access to
initial web request, which may be useful for performing authentication or
collecting cookies. This function then returns a ServerApp
, describing the
main loop and an action to perform on socket disconnection.
A dictionary of functions that Engine.IO needs in order to provide communication channels.
ServerAPI | |
|
The application to run for the duration of a connected socket.
SocketApp | |
|
Interacting with Socket
s
send :: Socket -> PacketContent -> STM () Source
Send a packet to the client. This is a non-blocking write.
receive :: Socket -> STM PacketContent Source
Receive data from the client, blocking if the input queue is empty.
type SocketId = ByteString Source
The type of unique Engine.IO sessions. This is currently a base64-encoded random identifier.
getOpenSockets :: EngineIO -> STM (HashMap SocketId Socket) Source
Retrieve a list of all currently open Engine.IO sessions.
dupRawReader :: Socket -> IO (STM Packet) Source
Create a new IO
action to read the socket's raw incoming communications.
The result of this call is iteslf an STM action, which will called will return
the next unread incoming packet (or block). This provides you with a separate
channel to monitor incoming communications. This may useful to monitor to
determine if the socket has activity.
This is a fairly low level operation, so you will receive *all* packets - including pings and other control codes.
The Engine.IO Protocol
Packets
parsePacket :: Parser Packet Source
Parse bytes as an Packet
assuming the packet contents extends to the
end-of-input.
data PacketType Source
The possible packet types, as mentioned in the Engine.IO protocol documentation
Packet Contents
data PacketContent Source
The contents attached to a packet. Engine.IO makes a clear distinction
between binary data and text data. Clients will receive binary data as a
Javascript ArrayBuffer
, where as TextPacket
s will be received as UTF-8
strings.
Payloads
parsePayload :: Parser Payload Source
Parse a stream of bytes into a Payload
.
:: Bool | If true, all bytes can be used. Otherwise, the packet will be base 64 encoded. |
-> Payload | |
-> Builder |
Encode a Payload
to a Builder
. As with encodePacket
, the
first argument determines whether or not binary transmission is supported.
Transport types
data TransportType Source
The possible types of transports Engine.IO supports.
parseTransportType :: Text -> Maybe TransportType Source
Attempt to parse a TransportType
from its textual representation.